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.
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.
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.
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!
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.
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.
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.
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.)
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.
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?
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.
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
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.
I think a function with 20+ effects is probably a “code smell”, regardless how you pass the handlers around. It may mean that:
The effects are too fine-grained.
For example, two separate effects Stdin and Stdout instead of Console (which combines both) may not buy you much unless you actually need the flexibility.
Effects deep down in a call stack are propagated all the way to the high-level functions.
In large code bases, propagating a type change transitively to all of the use sites can cause a massive amount of churn and headache.
Solutions may be:
Combining multiple effects into larger ones.
In the example above, structured concurrency, concurrency, and logging may be combined in a single effect if a lot of code use them in combination.
Modeling entire parts of the program as effects.
If I have an message loop that receives RPC messages and calls handlers (maybe provided as callbacks), instead of propagating all of the effects of all of the message handlers to the type signature of the message loop, I may implement an effect with message handling operations. Handlers/interpreters would then use other effects in the use site of the loop, but the message loop function itself would not have to be updated with effects of message handling code as they are updated.
(This effectively separates the code for the message loop and handling the messages, which may not always be desirable.)
A type-synonym-like approach for naming a collection of effects, and using that name in the call sites (transitively) might make this more manageable. If I start using a new effect deep down in a call stack, I can update the type synonym, and if all the callers also use I don’t have to change them, until the code that needs to handle the new effect.
(I suspect this is probably not possible with the type system features of GHC today, but just an idea, perhaps for another library or language.)
It’s actually fine, with ConstraintKinds you can write type AppE es = (Effect1 :> es, Effect2 :> es, Effect3 :> es) and then use AppE es in relevant contexts.
Note that using ConstraintKinds in this way has two related downsides:
You lose fine-grained “unused constraint” warnings from GHC
You lose some of the benefit of “saying what the function does not do”, since you will tend to “over-empower” functions to do things that they don’t actually need to do
Added makeOp and useImplUnder and recommend them as the way of making dynamic effects. This is more uniform than before, because it extends to dynamic effects that take handles as arguments.
Whoa, unused constraint warnings? That’s amazing! One of my biggest struggles with effectful is that I don’t realize when there are unused effects in the constraints. I’m going to have a wonderful time enabling that warning and laughing maniacly while sweeping all the redundant effects from the code base where I use effects.
On a more serious note, I’d argue against grouping together as well. Listing all effects in a function, be it constraint or arguments, will tell you a lot about what a function, and its transitive calls will do. The absence of an effect tells you what kind of stuff a function won’t do. Questions like “will this touch the database?” would otherwise be answered by a lot of go-to-source.
Having a lot of effects in a type signature could still say something about the cohesion of the function. Maybe it just does too much, and some of the effect uses can be extracted out to another function. To me, effects push (but do not force!) me to think about that more. That does not globally apply though. The functions closest to your runEff will likely still be sitting on a big pile of effects.
I am interested in how the so-called interpose operation can be used in bluefin.
The interpose operation plays a central role in dynamic effects.
It allows for locally modifying the behavior of an effect handler within the scope enclosed by interpose, and can be considered a kind of generalization of the Reader’s local operation.
When users hear that “dynamic effects are possible,” they will expect the functionality provided by interpose.
interpose is usually used as follows:
modifyPlus1 :: Reader Int :> es => Eff es a -> Eff es a
modifyPlus1 = interpose \case
Ask -> (+1) <$> ask
Local f m -> local f m
main = runReader 0 $ modifyPlus1 $ print =<< ask
-- > main
-- 1
In practical terms, for example, it can be used to add logging locally after the fact to an effect:
logWriteDB = interpose \case
WriteDB ... -> do
writeDB ...
log "Wrote to the DB"
Now, in effectful, there is an interpose function at Effectful.Dispatch.Dynamic. On the other hand, it seems that bluefin currently does not have this functionality for general effects, but if you have any ideas, please let me know.
My guess is that (considering that bluefinexplicitly propagates evidence via arguments* instead of implicitly holding the environment in a ReaderT IO), in bluefin it would theoretically take the following form:
modifyPlus1
:: Reader Int :> es
=> Reader Int e
-> (Reader Int e -> Eff (e :& es) a)
-> Eff (e :& es) a
modifyPlus1 r f = f $ r{ask = (+1) <$> ask r}
newtype Reader r e = MkReader { ask :: ? r } -- Not quite sure what to do here...
* It seems I had a slight misunderstanding… What bluefin carries around isn’t the handler functions, but just an IORef, right?