Replies: 4 comments 3 replies
-
The #!/usr/bin/env nix-shell
#!nix-shell -i runghc -p "ghc.withPackages (p: with p; [ effectful-core effectful-plugin ])"
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fplugin=Effectful.Plugin #-}
module Main (main) where
import Data.Kind (Type)
import Effectful
import Effectful.Dispatch.Static
data Unique (u :: Type) :: Effect
type instance DispatchOf (Unique u) = Static NoSideEffects
newtype instance StaticRep (Unique u) = Unique [u]
runUnique :: [u] -> Eff (Unique u : es) a -> Eff es a
runUnique us = evalStaticRep (Unique us)
fresh :: Unique u :> es => Eff es u
fresh = stateStaticRep \case
Unique [] -> error "fresh: empty list"
Unique (u : us) -> (u, Unique us)
main :: IO ()
main = do
runEff . runUnique [1 :: Int .. 3] $ do
u1 <- fresh
liftIO $ print u1
u2 <- fresh
liftIO $ print u2
u3 <- fresh
liftIO $ print u3
u4 <- fresh
liftIO $ print u4
-- $ ./unique.hs
-- 1
-- 2
-- 3
-- unique.hs: fresh: empty list
-- CallStack (from HasCallStack):
-- error, called at unique.hs:29:16 in main:Main |
Beta Was this translation helpful? Give feedback.
-
You can do what @evanrelf suggested (seems you also need instances of MonadUnique and MonadCheckpoint). It's sufficient if there's only going to be one way to use UniqueMonad/CheckpointMonad. If there can be multiple implementations, then this case seems to belong more in this category. Although these cases overlap a little, so I can see the confusion. I probably should improve the description a bit. If you go this route, the linked example in the docs should be pretty clear. You need to create a dynamic effect and a handler that reinterprets State. |
Beta Was this translation helpful? Give feedback.
-
Hi @evanrelf thanks for the code example. I kind of understand it on it's own. Though it still confuses me in the larger context of my question because there is no type that is the same like the code i want to make compatible. For example. Library code type Unique = Int
newtype UniqueMonadT m a = UMT { unUMT :: [Unique] -> m (a, [Unique]) } Example code Unique [u] So if i try to make that, i get something like But where i am really getting lost is where Was the example intended as reimplementation of the library or as an example of how to make it compatible with the library? I don't want to change library code at this point in time. And in general it is good to know how to use effectful with library code that is written by someone else or you otherwise have no control over. @arybczak thanks for your answer.
What do you mean? Implementation of what part exactly? I hope i only need to write "adapter code" from 1 monad transformer to effectful once. Not sure why would one want to have multiple implementations.
I like to have static dispatch because i believe it is more performant. I do understand what dynamic dispatch is but at this moment i can not think of an example why i would want to have dynamic dispatch. i.e. a feature that is only possible with dynamic dispatch. About the Dynamic approach in the example runDummyRNG :: Eff (RNG : es) a -> Eff es a
runDummyRNG = interpret $ \_ -> \case
RandomInt -> pure 55 instead of instance RNG :> es => MonadRNG (Eff es) where
randomInt = send RandomInt |
Beta Was this translation helpful? Give feedback.
-
@evanrelf well thanks anyway the code was inspirational. Yes i was looking for Integration with existing libraries. Do you know of a good example of integration with an existing library other than an example with IO such as resourceT? |
Beta Was this translation helpful? Give feedback.
-
Following the guide. Given this monad monad transformer that does no IO and has an internal state of
[Unique]
.The types are doable.
but then for the run function i'm lost. Looking at runResource for inspiration. Some questions/remarks:
unEff
uses IO. What alternative for unEff should be used?Library looks interesting, it's a bit steep learning curve on a first try.
Beta Was this translation helpful? Give feedback.
All reactions