Perhaps this is more motivating: implementing withArgs :: [String] -> Eff es a -> Eff es a
.
Statically, this seems pretty easy (I hope I did this correctly):
type Environment :: Effects -> Type
newtype Environment e = MkEnvironment (IOE e)
getArgs :: (e :> es) => Environment e -> Eff es [String]
getArgs (MkEnvironment ioe) = effIO ioe Env.getArgs
withArgs ::
(e :> es) =>
Environment e ->
[String] ->
Eff es a ->
Eff es a
withArgs (MkEnvironment ioe) xs eff =
runEffReader ioe $
withRunInIO $
\runInIO -> Env.withArgs xs (runInIO . toReader $ eff)
runEnvironmentIO ::
forall envEff es r.
(envEff :> es) =>
IOE envEff ->
(forall e. Environment e -> Eff (e :& es) r) ->
Eff es r
runEnvironmentIO ioe k = unsafeRemoveEff (k $ MkEnvironment ioe)
toReader :: Eff es a -> EffReader r es a
toReader = effReader . const
-- example usage
useArgs ::
( e1 :> es,
e2 :> es
) =>
IOE e1 ->
Environment e2 ->
[String] ->
Eff es ()
useArgs ioe env args =
withArgs env args $ do
argsIn <- getArgs env
-- use args
But imo it is completely reasonable to also offer a dynamic variant (e.g. testing, modifying specific args). In effectful
, this is straightforward:
data Environment :: Effect where
GetArgs :: Environment m [String]
WithArgs :: [String] -> m a -> Environment m a
type instance DispatchOf Environment = Dynamic
withArgs ::
(Environment :> es) =>
[String] ->
Eff es a ->
Eff es a
withArgs args = send . WithArgs args
runEnvironment :: (IOE :> es) => Eff (Environment : es) a -> Eff es a
runEnvironment = interpret $ \env -> \case
GetArgs -> liftIO Env.getArgs
WithArgs args m -> localSeqUnliftIO env $ \runInIO ->
liftIO $ Env.withArgs args (runInIO m)
This is an IO
interpretation, but we could just as easily give it any custom behavior we want.
Now, how do I do this in bluefin
? The naive translation almost works:
type Environment :: Effects -> Type
data Environment es = MkEnvironment
{ getArgsImpl :: Eff es [String],
withArgsImpl :: forall a. [String] -> Eff es a -> Eff es a
}
getArgs :: forall e es. (e :> es) => Environment e -> Eff es [String]
getArgs e = useImpl @e @es (getArgsImpl e)
withArgs ::
forall es a.
Environment es ->
[String] ->
Eff es a ->
Eff es a
withArgs e xs eff = useImpl (withArgsImpl e xs eff)
runEnvironmentIO ::
forall envEff es r.
(envEff :> es) =>
IOE envEff ->
(forall e. Environment e -> Eff (e :& es) r) ->
Eff es r
runEnvironmentIO ioe k =
useImplIn
k
MkEnvironment
{ getArgsImpl = effIO ioe Env.getArgs,
withArgsImpl = \xs eff ->
runEffReader ioe $
withRunInIO $
\runInIO -> Env.withArgs xs (runInIO . toReader $ eff)
}
useArgs ::
( e1 :> es,
e2 :> es
) =>
IOE e1 ->
Environment e2 ->
[String] ->
Eff es ()
useArgs ioe env args = do
argsBefore <- getArgs env
Utils.putStrLn ioe ("before: " ++ show argsBefore)
-- - Couldn't match type ‘e2’ with ‘es’
-- Expected: Environment es
-- Actual: Environment e2
--withArgs env args $ do
-- argsIn <- getArgs env
-- Utils.putStrLn ioe ("withArgs: " ++ show argsIn)
argsAfter <- getArgs env
Utils.putStrLn ioe ("after: " ++ show argsAfter)
Alas, the actual usage does not typecheck. Second attempt:
data Environment es = MkEnvironment
{ getArgsImpl :: Eff es [String],
withArgsImpl :: forall e a. [String] -> Eff (e :& es) a -> Eff es a
}
withArgs ::
forall es e a.
Environment es ->
[String] ->
Eff (e :& es) a ->
Eff es a
withArgs e xs eff = useImpl (withArgsImpl e xs eff)
runEnvironmentIO ::
forall envEff es r.
(envEff :> es) =>
IOE envEff ->
(forall e. Environment e -> Eff (e :& es) r) ->
Eff es r
runEnvironmentIO ioe k =
useImplIn
k
MkEnvironment
{ getArgsImpl = effIO ioe Env.getArgs,
withArgsImpl =
\xs eff -> error "???"
-- • Couldn't match type ‘es’ with ‘e :& es’
-- Expected: Eff (e :& es) a -> EffReader (IOE envEff) es a
-- Actual: Eff (e :& es) a -> EffReader (IOE envEff) (e :& es) a
-- runEffReader ioe $
-- withRunInIO $
-- \runInIO -> Env.withArgs xs (runInIO . toReader $ eff)
}
But I couldn’t figure out the interpeter. Finally, I attempted to change withArgsImpl
to something like:
withArgsImpl :: forall a. [String] -> (forall e. Environment e -> Eff (e :& es) a) -> Eff es a
But, again, I was not able to get this to work. Is this possible? I have the code up here: GitHub - tbidne/bluefin-higher-order.