-
Here is my use case:
However, in
I think a workaround is to relax Edit: I think I know why it is nominal in the first place. The static effects relies on the |
Beta Was this translation helpful? Give feedback.
Replies: 2 comments 1 reply
-
Not sure, but for your use case (as I understand it) the Labeled effect might be useful: {-# LANGUAGE GHC2021 #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
module ByteWriter where
import Prelude
import Data.ByteString.Builder (Builder)
import Effectful
import Effectful.Labeled (Labeled, labeled, runLabeled)
import Effectful.Writer.Static.Local (Writer, runWriter, tell)
type ByteWriter tag = Labeled tag (Writer Builder)
runByteWriter :: Eff (ByteWriter tag ': es) a -> Eff es (a, Builder)
runByteWriter = runLabeled runWriter
writeBytes :: forall tag es. (ByteWriter tag :> es) => Builder -> Eff es ()
writeBytes builder = labeled @tag @(Writer Builder) (tell builder)
writeSomeStuff :: IO ()
writeSomeStuff = do
output <- runEff
. runByteWriter @"group1"
. runByteWriter @"group2"
$ do
writeBytes @"group1" "write"
writeBytes @"group2" "some"
writeBytes @"group1" "stuff"
print output -- Output: (((),"some"),"writestuff") If you are using GHC 9.10 then you can also use visible dependent quantification to get rid of {-# LANGUAGE GHC2021 #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RequiredTypeArguments #-}
module Labeled2 where
import Prelude
import Data.ByteString.Builder (Builder)
import Effectful
import Effectful.Labeled (Labeled, labeled, runLabeled)
import Effectful.Writer.Static.Local (Writer, runWriter, tell)
type ByteWriter tag = Labeled tag (Writer Builder)
runByteWriter :: forall tag -> Eff (ByteWriter tag ': es) a -> Eff es (a, Builder)
runByteWriter _tag = runLabeled runWriter
writeBytes :: forall tag -> (ByteWriter tag :> es) => Builder -> Eff es ()
writeBytes tag builder = labeled @tag @(Writer Builder) (tell builder)
writeSomeStuff :: IO ()
writeSomeStuff = do
output <- runEff
. runByteWriter "group1"
. runByteWriter "group2"
$ do
writeBytes "group1" "write"
writeBytes "group2" "some"
writeBytes "group1" "stuff"
print output -- Output: (((),"some"),"writestuff") |
Beta Was this translation helpful? Give feedback.
-
You shouldn't 🙂
I see you've figured it out in the EDIT already, but just to confirm: this doesn't work because of StaticRep as you can wrap a static effect into a newtype and give it a completely different StaticRep instance. |
Beta Was this translation helpful? Give feedback.
Not sure, but for your use case (as I understand it) the Labeled effect might be useful: