Bluefin compared to effectful [video]

I gave a talk to CircuitHub about the differences between the Bluefin and effectful effect systems for Haskell:

28 Likes

Pleasure having you @tomjaguarpaw - we all found this really interesting!

5 Likes

Thanks to the both of you for making this public. There was a question in the talk about -XImplicitParameters not working for some reason. I also wonder whether reflection could be an option to temporarily kick an effect handle up to the type level, or whether that hits similar issues?

2 Likes

That would be nice, but I haven’t managed to make it work. Here are some branches with the experiments.

The reason that it’s difficult to make work is that successful type class resolution is vital for ergonomics, and that’s very delicate. I think the most likely thing to work would be to either have an effectful-style effect handle that gives you access to value level effects, or to have two type parameters. The effectful-style version ends up with operations with types like this:

op ::
  ( e :> es,
    e1 :> es,
    St.State Int ::> es',
    Er.Error String ::> es'
  ) =>
  State Int e1 ->
  Effectful es' e ->
  Eff es Int

The two type parameters version would look like

data Eff2 es1 es2 r

op ::
  ( e :> es2,
    e1 :> es2,
    St.State Int ::> es1,
    Er.Error String ::> es1
  ) =>
  State Int e1 ->
  Effectful es' e ->
  Eff2 es1 es2 Int

I don’t intend to spend much time on this because, despite the first question about Bluefin always being “But don’t you get tired of passing effects at the value level? Isn’t there a way of passing (some of) them implicitly?”, no, in all of my use of Bluefin so far I have not (yet?) wished that I could pass effects at the type level. I actually prefer having everything at the value level.

1 Like

Thanks for making the presentation showcasing how effects are an improvement over the ReaderT pattern or transformers/mtl.

I have a few comments.

“Bluefin takes streaming seriously” slide

The text “you cannot do this in effectful” is misleading. As pointed out shortly after, the reality is there is simply no such effect in the effectful-core and effectful package, nothing prevents someone interested in streaming to experiment with how the API should look like and publish their own effectful-streaming (or something) library. Considering that there exist multiple streaming libraries with large APIs that were developed and polished over the years, I suspect providing a good streaming API as an effect is not as easy as you make it out to be, but perhaps I’m wrong.

“Positives for effectful and Bluefin” slide

  • Inference is better - no argument there. Poor inference with multi-parameter effects is my main gripe with effectful. effectful-plugin solves the problem, but it would be nice to have a solution that doesn’t require a plugin. Maybe one day I’ll have a brilliant idea or something.

  • Creating new effects is just creating new data types (“normal Haskell”) - the same is true for effectful, the only difference is the representation - product types vs sum types.

  • Streams - again, it’s just an effect that exists in the bluefin package and not in the effectful-core/effectful package. The effectful package has multiple effects that bluefin doesn’t, but it’s not mentioned (and rightly so), so I’m not sure why this particular one is.


Let’s talk about downsides. The main ones of effectful IMO at the moment are:

  1. Poor inference with multi-parameter effects without a plugin. As mentioned above, plugin fixes this, but ideally it shouldn’t be needed.

  2. Awkward interoperability between regular effects and their labeled counterparts. In bluefin all effects are labeled (at the term level) and this uniformity is nice.

If it comes to bluefin, IMO its major issues are:

  1. Passing effects as arguments.
  2. Unclear story for higher order effects.
  3. No good story for interop with MTL style effects.

Re (1), it looks nice in small examples since you can clearly see where the effects go and there are no inference issues. However, if effects are embraced in a non-trivial code base, there’s going to be quite a few of them. As @michaelpj pointed out, their code base has functions with 20+ effects, passing these explicitly won’t work. I personally developed at work a small-ish service with a limited scope with effectful and functions there use around 5-10 effects, that’s already too much for explicit passing.

You can probably create a bunch of data types and pack your effects into groups and pass a single parameter, but then at some point you will have to add or remove some or refactor the code and dabble in it again, not great.

Re (2), see this ticket. A good, simple litmus test for higher order effects is here - you run Reader, then use ask in a downstream handler and later you can call local to influence the behavior of the handler. Not sure how that would look in bluefin (one can be tempted to use State with IORef underneath instead, but what if you then add forkIO to the equation?). There was actually a question from @ocharles about local at the end of the presentation that went unanswered.

Re (3), see this ticket. When you look at bluefin’s Eff, it pretty much has no instances (compare that to instances of the effectful’s Eff). How do you run MonadIO or MonadFail stuff? There are some special functions for this with very limited usability (because m is universally quantified in the continuation). You have a function f :: (MonadIO m, MonadFail m) => m ()? You can’t run it easily in bluefin’s Eff. This also means that you will most likely have a bad time trying to run any library/code that uses mtl style effects and there is a lot of such code out there.

12 Likes

I’ve been so far mainly on the “Just use IO” side, not just not only because I think IO is enough but also because I think the solutions are not granular enough (I’ll come to that later)
However I found that video excellent and I realized that they are situations when using IO is not enough, so here are my two cents.

I really like the simplicity of Bluefin and how having explicit handles makes types simpler, type errors potentially clearer and how it highlights the exact location of effects.
I was sold until @michalpj came up with the 23 effects issue. I was a bit shocked at first, 23 effects seems unreasonable then realized that it is the reason d’etre of effect system (and my main argument against):
How far do we go, how fine are the grains ? If we can only handle half a dozen “grains”, then they should be called pebbles (I am generous) but not fine-grain.

I don’t do complicated networking things with lots of shared resources with exception thrown left, right and center. What I do is main read stuff from files and/or database, do (clever) pure stuff with it and saven it back to files/db etc …
In my case “Just use IO” works, the business logic (where I need the code to be safe) is in the (clever) pure stuff. However, I could do with really fine grain effects to deal with database permission, read/write access per table and possible columns.
I would like to know if that particular function is using that particular table, or it modifies the price or the description of an item in the database.
We are talking there about hundreds possibly thousands of effects. With Bluefin I might be able to bundle handles together but that will break encapsulation : how do we guarantee that all handles are used ?
The point is : the finer the grains become the less Bluefin becomes attractive (which defeats the object).

About using the same effect twice (as using two states), even though it might be handy and look like a nice feature I am not sure it’s a good thing.
Like IO it makes senses to have only one effect of a type. State Int may not be called “effect” until associated with a semantic as it’s stand
it should be more seen as a effect “constructor”.

It is also a shame that implicit parameters don’t work, IP seemed the perfect way to switch between constraint (ala Effectfull) and explicit parameters.

Having said that, I can see how when dealing with a few “grains” Bluefin can work really well.

My last comment would be regarding using record could be beneficial.
If I’fm fcorrect pretty much all Bluefin function take an effect as first argument. If the effect was a record and the function its fields one could do
(using the appropriate records extensions)

runPureEff $ withEarlyReturn $ \EarlyReturn{..} -> do
  for_ [1 .. 10] $ \i -> do
    when (i >= 5) $
      returnEarly ("Returned early with " ++ show i)
  pure "End of loop"

instead of

runPureEff $ withEarlyReturn $ \e -> do
  for_ [1 .. 10] $ \i -> do
    when (i >= 5) $
      returnEarly e ("Returned early with " ++ show i)
  pure "End of loop"
1 Like

It may be less bad than you fear. Go back to ST: we have

runST :: (forall s. ST s a) -> a
newSTRef :: a -> ST s (STRef s a)

Using newSTRef we can make zillions of STRefs all tagged with the same “state thread” s. Then one runST (and in Bluefin one constraint) serves to encapsulate all of those STRefs.

In Bluefin terms we might say

newRegion :: (∀ s. Region s -> Eff (s :& es) b) -> Eff es b
newRef :: ∀ s es.  (s :> es) => a -> Region s -> Eff es (Ref s a)

where Region e is the capability (permission to create references in region s) but you can make zillions of Ref (in Bluefin they are called State) cells in that region. Then newRegion encapsulates them all at once.

Same with exceptions. I don’t know if Bluefin lets you do this but it could: have an “exception region” and the you can encapsulate a whole class of exceptions in one go.

You can pick the granularity to suit your application

3 Likes

About the 20-effect function. I don’t know if it was the case here, but a common way such functions come to be is by making them reflect “transitive dependencies” in their signatures. They have to manage not only their immediate dependencies, but the dependencies of all the other functions that they call. Adding a new dependency in a function deep below in the call hierachy often requires a painful and tedious refactor, as the constraints are propagated upwards to all callers.

I’m very OOP-brained when it comes to the large-scale structure of applications. When using OOP (often in combination with some type-directed dependency injection framework) each function/component only receives the components (here they would be called “effects”) that it directly uses. Such components might have their own dependencies, but when a component is injected elsewhere, it will already have been fully constructed. The consumers of the component don’t need to care about what ingredients were required for its construction.

I’m not sure how the same principle applies to effect systems. Likely it requires converting direct function calls into separate effects. So the number of effects will increase, but hopefully they will serve as “seam” that prevents excessive concentration of dependencies. Perhaps Bluefin.Compound could help with that.

1 Like

If I understand well you are talking of “dynamic” effects (which can be created on the fly) whilst I am thinking “static” effects (where each one as a “name” and is visible to the type system). For example with a db of 23 tables , each effect would relate to the permission of using one table and a function using all tables would look like

 read23Table :: e1 :> es
             => e2 :>  es
             => ... => e23 :> es 
             => ReadTable1 e1 -> ReadTable2 e2 -> ... -> ReadTable23 e23
             -> Eff es a

In any case, bundling effects together makes us loose the ability to know if a particular effect is used or not.

I’m pretty sure you can do that with Has pattern.

 read23Table :: e :> es
             => HasReadTable1 db
             => HasReadTable2 db
             => ... => HasReadTable23 db 
             => db e -> Eff es a

If it is a win, I don’t know. But you went from “Just use IO” to “possibly thousands of effects”. I’d stop at “read db”, “write db” and “no db”, and that seems manageable and meaningful. I’d also bet that, famous now, 23 effect function, doesn’t actually do anything other than delegating the work to less than 23 effect functions, where the “fine-grain” actually happens. I mean, it is not really interesting that runApp or handleRequest does all the things, it is interesting what createUser does.

3 Likes

It might be interesting to get a bit concrete with the 23-effect function. So here is a list of the effects (annotated and lightly redacted)!

  ( Concurrent :> es -- standard from 'effectful'
  , IOE :> es -- standard from effectful
  , Statement :> es -- DB statements
  , DB :> es -- DB transactions
  , Trace :> es -- opentelemetry tracing
  , AWS :> es -- AWS
  , Log :> es -- `log-base` compatibility via 'log-effectful'
  , StructuredConcurrency :> es -- ki compatibility via 'ki-effectful'
  , Labeled "backgroundTasks" (Reader Ki.Scope) :> es -- ki scope for background tasks
  , Resource :> es -- resourcet via 'resourcet-effectful'
  , Time :> es -- time access via 'monad-time-effectful'
  , Retry :> es -- retrying via 'retry-effectful'
  , Writer T :> es -- locally used to track work we didn't finish
  -- plus
  -- 4 internal effects relating to specific computer vision tasks
  -- 3 internal effects relating to global subsystems
  -- 2 minor utility custom effects
  )

What I think is interesting here is that I don’t think it’s the case that this is extraordinarily fine-grained. Maybe some of the DB effects could be lumped together; and it’s kind of annoying that we have both Concurrent and StructuredConcurrency. But pretty much everything else corresponds to different, quite substantial things that this function needs.

Now of course some of this can be split up: we do generally have separate functions that fetch what we need from the database, and then other functions that consume it. But this is (nearly) a top-level one, so has pretty much everything.

So possibly it’s just that we have to do an unusually large amount of stuff. But I also think it’s not too hard to hit 10+ effects while doing only a reasonably large amount of stuff: a few standard effects, plus some database effects, plus a couple of custom ones and you’re there!

10 Likes

And I would like to thank you for two things which were essential components in the development of Bluefin: firstly developing effectful itself, and demonstrating that a well-typed IO-based effect system was possible, and secondly, your comment on Reddit that made me realize that that was the correct approach for Bluefin too, not delimited continuations.

Perhaps misleading, but as you say, out of the box it is indeed not possible. I think every effect system should provide lightweight streaming as a first class citizen. It is a wonderfully-powerful abstraction!

I think it is easy, and I think Bluefin does it. There are some features it does not provide (those based on consuming elements from a stream individually – but then again those are not safe anyway, in streaming etc. You need linear types to make them safe.) but it does provide 90% of what you want from a streaming API, and even reimplements 90% of the pipes API directly!

In fact, what Bluefin provides is even better than streaming and pipes because Bluefin streams are code, not data: no risk of accidentally materializing your stream and getting a space leak.

Interesting to know. I wonder if a plugin could also help in the cases where Bluefin type inference breaks down. I’ll have to look into it.

Ah, that’s really understating the case! Suppose I want a (static) compound effect that combines state and exceptions. In Bluefin I just write a data type to do that:

data Combined e =
    MkCombined (State Int e) (Exception String e)

Or suppose I want a dynamic effect that supports writing Ints and reading Strings. Then I just define

data Combined2 e =
  MkCombined2 (Int -> Eff e ()) (Eff e String)

That’s it! There were things that I wanted. I wrote them.

Now how do I do the same in effectful? The first, well, I’m not really sure I can. Can I? I can do

type Combined e = (State Int :> e, Exception String :> e)

but that leaks the internals. Maybe that’s OK. I could define a new class

class (State Int :> e, Exception String :> e) =>
  Combined e

instance (State Int :> e, Exception String :> e) =>
  Combined e

but I’m not sure that plays well with type checking.

The second, I have to do:

data Combined2
  WriteInt :: Int -> Combined2 m ()
  ReadString :: Combined2 m String

This is really very indirect! I didn’t want an ADT with WriteInt and ReadString fields. I just had to write them to get what I really wanted.

Granted, the Bluefin story isn’t as simple as I make out either, there’s a bit of massaging you have to do to get the types to work out. But it is much more direct than the effectful story.

It’s because I find streaming so useful. I don’t understand how others can do without it. About half of the lists I create now, I create using streaming. I think until you have access to a lightweight streaming abstraction it’s hard to know just how useful it is.

Yes, fair enough. If you have 10 or 20 effects, and you don’t want to abstract them into coarser-grained effects, then Bluefin won’t help you. I personally haven’t come across this use case (in fact I’d work hard to not have it happen) but perhaps it’s a matter of taste.

Do you mean the question at around 1:01:00? I believe it was answered around 1:03:00. Or are there still issues left unresolved?

I still haven’t managed to understand what a “higher order effect” actually is. My current best guess is that a higher order effect is just a handler, but for path dependent reasons they have been conferred with special status. I haven’t yet come across a higher order effect that I couldn’t obtain just by using a handler. For example, a Bluefin “reader local” is just

import Bluefin.Eff
import Bluefin.Reader

local ::
  e1 :> es =>
  Reader r e1 ->
  (r -> r) ->
  (forall e. Reader r e -> Eff (e :& es) z) ->
  Eff es z
local re f k = do
  r <- ask re
  runReader (f r) k

I have yet to understand why this is such a marvellous and important construction, but I will keep trying.

Either I have missed something, higher-order effects are terribly important and thus Bluefin is terribly flawed, or higher-order effects are really nothing special, people got tied up in knots chasing their tail about them (for path dependent reasons) and Bluefin is simpler because it doesn’t try to shoehorn them in. Of course the former is possible, but my hunch is that it’s the latter than pertains.

I haven’t worked on this because it hasn’t been particularly important to me. Perhaps it’s important to someone else. If so they can open an issue and I’ll make a nice story about it.

That’s said, MTL compatibility is important for converting legacy code to effectful/Bluefin but is of basically no utility for new code. If you’re writing an MTL-style operation, and you use an effectful/Bluefin handler, you are then immediately out of the MTL world forever. There’s no way of going back. Nor is there a way of using a native effectful/Bluefin effect and going back into the MTL world. So I can’t imagine that there’s a huge demand for flexible MTL compatibility, and if there’s not then a newtype escape hatch seems simple and good enough, for example:

newtype MyEffect r =
  MkMyEffect (forall e. State s e -> Exception ex e -> Eff e r)

instance (MonadState s) MyEffect  where ...
instance (MonadError ex) MyEffect where ...

This sounds very similar to me to making compound effects/effect abstraction. @maxigit says it “breaks encapsulation”, but to me it seems fine.

I think @maxigit explicitly does not want this, as explained below (using the terminology “breaking encapsulation”). Using Region to abstract Bluefin’s State effects is a sort of “coarse graining”. @maxigit wants “fine grains”. Personally, I don’t. But it seems some people (including CircuitHub, with their 20 grains) do.

1 Like

The problem that higher order effects solve is that normal handlers force you to commit to one specific implementation of your effects. If you write the higher order local operation as a handler directly like in your example, then you are forcing this particular implementation on everyone who uses it. Users cannot choose later to give the effect a different meaning, which they can do with – and which is one of the main selling points of – normal algebraic operations.

The Hefty Algebras paper explains this problem and a sketch of a solution in Section 1.2 and 1.3.

1 Like

Perhaps, depending on how you define “one”. But that “one” can be can be a dynamic implementation, which can itself be filled in with the true, static, implementation somewhere else.

In any case, there can be no fundamental issue with higher order effects in Bluefin. If effectful can support them, Bluefin can support them. I just don’t see the point yet (because I don’t understand what they are or why they’re needed).

Perhaps the Hefty paper will explain it. I’ll take a look. Thanks for the link.

Your example hard codes the r <- ask re; runReader r k behavior. I don’t think you can change that as as a caller of the local operation.

1 Like

Oh, that example is a static one, sure, but in general I don’t see why one couldn’t provide an implementation that can be dynamically swapped. Could you give a more complex example of a higher-order effect? I think I’m being blinded by the simplicity of local, which does essentially nothing, so it’s probably not a very good exemplar.

Looking at your local example, I’m actually confused about what it is supposed to do. The local I know allows you to locally alter the value that is read by the reader, which is nicely captured by its usual type signature local :: MonadReader r m => (r -> r) -> m a -> m a, but in your case you don’t seem to alter anything.

I think local should be good enough to show the workings of higher order effects. MonadReader in mtl does have local as a higher order operation that you can overload with your own instance. For example, you can choose not to apply the function:

newtype R r a = R (r -> a) deriving Functor deriving (Applicative, Monad) via ... 

instance MonadReader r (R r a) where
   ...
   local _ x = x

This handler changes the meaning of all uses of local in all existing programs written in the overloaded mtl style.

Can you define a local operation that allows you to delay the choice of whether or not to apply the context-modifying function to the time when the user applies the handler?

(This case is indeed a bit too simple, because I guess you could simply add a boolean in the record to indicate whether or not to apply the function, but what if someone comes around later and wants some different kind of behavior, like applying the function n times? You could change the boolean to a natural number, but does that capture all possible behaviors? I hope you can agree that a solution like that won’t work for all higher order operations.)

3 Likes

Oh yes, I beg your pardon, it should be this:

local ::
  e1 :> es =>
  Reader r e1 ->
  (r -> r) ->
  (forall e. Reader r e -> Eff (e :& es) z) ->
  Eff es z
local re f k = do
  r <- ask re
  runReader (f r) k

Right, OK, I’m beginning to understand. The local I gave above is a static one, and the goal is to be able to use local dynamically, i.e. dispatch to a version that is passed in from somewhere else.

I have two separate responses.

  1. Why? I’ve never used listen, pass, censor etc. and don’t feel like I’ve missed out. Have I? What do people use them for?

  2. Can’t you just pass the thing you want to the place you want it? If you want something with the type of local can’t you define

    data Local r = MkLocal (
      forall e1 es z.
      e1 :> es =>
      Reader r e1 ->
      (r -> r) ->
      (forall e. Reader r e -> Eff (e :& es) z) ->
      Eff es z)
    

    and then pass it to the use site and then use it? I don’t understand what’s difficult about this at all.

Maybe my confusion in 1 is due to 2. The solution seems so simple that I don’t understand why there would be a whole special notion for it. Perhaps the issue is the “path dependence” I mentioned. MTL’s local is

MonadReader r m where
  local ::
    (r -> r) ->
    m a ->
    m a

This doesn’t give you any way to refer to the “other untouched effects” inside m. You can only refer to the entire monad. Bluefin, by contrast, does allow you to mention es, so I think life is much easier. (effectful allows the same and I guess so do polysemy and similar – this isn’t anything to do with being IO-based.)

My working hypothesis is that MTL made doing this difficult, so it became a “topic of interest” and was given a name of its own, but if we’d started in an “effect tagging” world instead then it would never had arisen as an issue.

1 Like

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.

1 Like

Great example! You were very close with your first try, but it should have been:

data Environment es = MkEnvironment
  { getArgsImpl :: Eff es [String],
    withArgsImpl :: forall a e. [String] -> Eff e a -> Eff (e :& es) a
  }

The reason for this is not explained well in the Bluefin.Compound documentation, though it there is a bit of discussion on a Bluefin issue. I wrote up the full implementation and submitted a PR. I even added a dynamic implementation that uses State under the hood, rather than IO! (I guess I could equally have used Reader since the args should probably not be written to). EDIT: Oh, Reader wouldn’t work because the “body” doesn’t take a parameter. Maybe it should. I don’t really understand the design space.

Currently the technique needed to implement this is a very flaky pattern. I need to make the pattern more solid, and then add library support so that there’s no more guesswork.

Output from the example runner:

% cabal run                                     
STATIC
before: []
withArgs: ["static","args"]
after: []
DYNAMIC3 IO
before: []
withArgs: ["dynamic3 io","args"]
after: []
DYNAMIC3 STATE
before: []
withArgs: ["dynamic3 state","args"]
after: []
1 Like