Bluefin compared to effectful [video]

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

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.)

6 Likes

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.

4 Likes

Note that using ConstraintKinds in this way has two related downsides:

  1. You lose fine-grained “unused constraint” warnings from GHC
  2. 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
3 Likes

This is great, thank you!

1 Like

@tbidne, based on your report of your experience I made some improvements.

  • Added withEffToIO_, which is the simplest IO unlifting operation.
  • Added documentation to the weird EffReader instance for MonadUnliftIO that withEffToIO_ should be preferred.
  • 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.
1 Like

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. :broom::broom:

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 bluefin explicitly 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?

5 Likes

I’m not sure that example is particularly interesting, because it only modifies ask. If you want to modify ask you can just use local! It seems that it is the examples that modify local that are interesting. such as your example at What is a higher-order effect? - #18 by ymdfield.

I’m not sure I understand fully what you mean, but what the handle actually is depends on the effect in question. You can see them all in the source. For example, State s is an IORef s, Reader is a State, Exception e is a forall a. e -> IO a that throws an exception, Coroutine a b is a function a -> Eff e b, etc., etc.

1 Like

Thank you for your explanation.

Yes, my explanation wasn’t very good here. modifyPlus1 is just a toy example to show how to use interpose itself, and you’re right that in this case, simply using local is sufficient. Rather, what I mainly should have asked about was logWriteDB. This is close to the code I showed in another thread, and it’s something used to take logs in a local, monkey-patch-like manner. By using interpose in this way, you can set up hooks for general effects in a unified manner, which I consider one of the convenient features of the effect system. So I’m hoping we can do this in bluefin as well. I’ll read the responses in that thread and think about it a bit more. Thank you.

It seems I was mistaken about it being just an IORef. Good to hear that it depends on the effect (especially interesting in the case of coroutines). Thanks!

1 Like

If you provide a simple, but fully-working, example then I’ll try to replicate it in Bluefin.

1 Like

I tried writing it in effectful-2.5:

{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

module Main where

import Effectful (Eff, Effect, IOE, MonadIO (liftIO), runEff, type (:>))
import Effectful.Dispatch.Dynamic (interpose_, interpret_)
import Effectful.TH (makeEffect)
import Prelude hiding (log)

data Log :: Effect where
    Log :: String -> Log m ()
makeEffect ''Log

runLog :: (IOE :> es) => Eff (Log ': es) a -> Eff es a
runLog = interpret_ \(Log msg) -> liftIO $ putStrLn $ "[INFO] " <> msg

type DBValue = String

data DB :: Effect where
    InsertDB :: DBValue -> DB m ()
makeEffect ''DB

runDummyDB :: (IOE :> es) => Eff (DB ': es) a -> Eff es a
runDummyDB = interpret_ \case
    InsertDB value -> liftIO $ putStrLn $ "[DummyDB.InsertDB] " <> value

hookLoggingInsertDBLocally :: (DB :> es, Log :> es) => Eff es a -> Eff es a
hookLoggingInsertDBLocally = interpose_ \(InsertDB value) -> do
    insertDB value
    log $ "Wrote to the DB: " <> value

suppressLog :: (Log :> es) => Eff es a -> Eff es a
suppressLog = interpose_ \(Log _) -> pure ()

-- > main
-- [DummyDB.InsertDB] value1
-- [DummyDB.InsertDB] value2
-- [DummyDB.InsertDB] value3
-- [INFO] Wrote to the DB: value3
-- [DummyDB.InsertDB] value4
-- [INFO] Wrote to the DB: value4
-- [DummyDB.InsertDB] value5
-- [DummyDB.InsertDB] value6
-- [DummyDB.InsertDB] value9
-- [DummyDB.InsertDB] value10
main :: IO ()
main = runEff . runLog . runDummyDB $ do
    insertDB "value1"
    insertDB "value2"
    hookLoggingInsertDBLocally do
        insertDB "value3"
        insertDB "value4"
    insertDB "value5"
    insertDB "value6"

    suppressLog do
        hookLoggingInsertDBLocally do
            insertDB "value9"

    hookLoggingInsertDBLocally do
        suppressLog do
            insertDB "value10"

Note that not only are we locally hooking logging with hookLoggingInsertDBLocally, but we’re also using interpose with suppressLog to locally suppress logging. Not only can we add processing, but we can also eliminate the effect itself. From the user’s perspective, we can write code with the intuition of “editing” a program where effects are written sequentially, without resorting to ad-hoc methods like managing state with Reader or State and writing branches with if statements. Imagine that this intuition can be used universally and directly, without being limited to specific effects or use cases. Personally, I think this is somewhat akin to metaprogramming.

If we achieve this in bluefin, I guess it would take the form of an idiom or design pattern where we locally swap or rewrite the value-level effects passed as arguments in some way. However, there might be aspects of bluefin that I’m not aware of that could come into play.

Also, you might not find such “hooks” to be particularly practical. Personally, I find these hooks to be quite convenient, especially for implementing “cross-cutting” concerns like logging, tracing, and profiling, although I acknowledge that I might have some personal bias.


Regarding the part where I said “universally”, ultimately this means being able to write a function that is polymorphic over effects, allowing you to add logging to any arbitrary effect, like the following:

hookLoggingLocallyForAnyEffect ::
    forall e es a.
    (e :> es, Log :> es, DispatchOf e ~ 'Dynamic, ShowEffect e) =>
    Eff es a -> Eff es a
hookLoggingLocallyForAnyEffect = interpose_ @e \e -> do
    r <- send e
    log $ "Effect executed: " <> showEffect e
    pure r

…Strictly speaking, this doesn’t typecheck at the send part (I’m a beginner with effectful…), but it should be possible in other libraries, so I think we can do something similar in effectful. Note that ShowEffect is a type class that would need to be defined separately.

2 Likes

…Strictly speaking, this doesn’t typecheck at the send part (I’m a beginner with effectful…),

It will work with Add passthrough by arybczak · Pull Request #274 · haskell-effectful/effectful · GitHub if you do this:

hookLoggingLocallyForAnyEffect ::
    forall e es a.
    (e :> es, Log :> es, DispatchOf e ~ 'Dynamic, ShowEffect e) =>
    Eff es a -> Eff es a
hookLoggingLocallyForAnyEffect = interpose @e \env e -> do
    r <- passthrough env e
    log $ "Effect executed: " <> showEffect e
    pure r

For the record, effectful's interpose also allows one to write purely dynamic handler for Reader:

runPureReader :: r -> Eff (Reader r : es) a -> Eff es a
runPureReader r0 = interpret (handler r0)
  where
    handler :: r -> EffectHandler (Reader r) handlerEs
    handler r env = \case
      Ask       -> pure r
      Local f m -> localSeqUnlift env $ \unlift -> do
        unlift $ interpose (handler $ f r) m

so it’s very powerful.

2 Likes

Thank you! I found that very helpful for writing this type of code in Bluefin. The structure of the implementation carries over directly, and I can confirm it has the exact same behaviour. One notable difference is that I explicitly use the H “mutable handle” (I’ll come up with a better name) rather than defining an interpose primitive.

Preamble
basicLog :: (e :> es) => BasicLog e -> String -> Eff es ()
basicLog b s = makeOp (basicLogImpl (mapHandle b) s)

runBasicLog ::
  (e1 :> es) =>
  IOE e1 ->
  (forall e. BasicLog e -> Eff (e :& es) a) ->
  Eff es a
runBasicLog io k =
  useImplIn
    k
    MkBasicLog
      { basicLogImpl = \msg ->
          effIO io $ putStrLn $ "[INFO] " <> msg
      }

type DBValue = String

newtype BasicDB es = MkBasicDB
  { insertBasicDBImpl ::
      forall e.
      DBValue ->
      Eff (e :& es) ()
  }

instance Handle BasicDB where
  mapHandle b =
    MkBasicDB
      { insertBasicDBImpl = \s -> useImplUnder (insertBasicDBImpl b s)
      }

insertBasicDB :: (e :> es) => BasicDB e -> DBValue -> Eff es ()
insertBasicDB d v = makeOp (insertBasicDBImpl (mapHandle d) v)

runDummyBasicDB ::
  (e1 :> es) =>
  IOE e1 ->
  (forall e. BasicDB e -> Eff (e :& es) a) ->
  Eff es a
runDummyBasicDB io k =
  useImplIn
    k
    MkBasicDB
      { insertBasicDBImpl = \value ->
          effIO io $ putStrLn $ "[DummyDB.InsertDB] " <> value
      }

type Log = H BasicLog

log :: (e :> es) => Log e -> String -> Eff es ()
log l msg = do
  b <- askH l
  basicLog b msg

runLog ::
  (e1 :> es) =>
  IOE e1 ->
  (forall e. Log e -> Eff (e :& es) a) ->
  Eff es a
runLog io k = do
  runBasicLog io $ \l -> do
    runH l $ \h -> do
      useImplIn k (mapHandle h)

type DB = H BasicDB

insertDB :: e :> es => DB e -> DBValue -> Eff es ()
insertDB d v = do
  b <- askH d
  insertBasicDB b v

runDummyDB ::
  (e1 :> es) =>
  IOE e1 ->
  (forall e. DB e -> Eff (e :& es) a) ->
  Eff es a
runDummyDB io k = do
  runDummyBasicDB io $ \d -> do
    runH d $ \h -> do
      useImplIn k (mapHandle h)

hookLoggingInsertDBLocally ::
  (e1 :> es, e2 :> es) =>
  DB e1 ->
  Log e2 ->
  Eff es a ->
  Eff es a
hookLoggingInsertDBLocally d l k = do
  orig <- askH d

  localH
    d
    ( MkBasicDB
        { insertBasicDBImpl = \value -> do
            insertBasicDB orig value
            log l $ "Wrote to the DB: " <> value
        }
    )
    k

suppressLog ::
  (e1 :> es) =>
  Log e1 ->
  Eff es a ->
  Eff es a
suppressLog l k = do
  localH
    l
    (MkBasicLog {basicLogImpl = \_ -> pure ()})
    k
-- > main
-- [DummyDB.InsertDB] value1
-- [DummyDB.InsertDB] value2
-- [DummyDB.InsertDB] value3
-- [INFO] Wrote to the DB: value3
-- [DummyDB.InsertDB] value4
-- [INFO] Wrote to the DB: value4
-- [DummyDB.InsertDB] value5
-- [DummyDB.InsertDB] value7
-- [DummyDB.InsertDB] value9
-- [DummyDB.InsertDB] value10
main :: IO ()
main =
  runEff $ \io -> runLog io $ \l -> runDummyDB io $ \d -> do
    insertDB d "value1"
    insertDB d "value2"
    hookLoggingInsertDBLocally d l $ do
      insertDB d "value3"
      insertDB d "value4"
    insertDB d "value5"
    insertDB d "value7"

    suppressLog l $ do
        hookLoggingInsertDBLocally d l $ do
            insertDB d "value9"

    hookLoggingInsertDBLocally d l $ do
        suppressLog l $ do
            insertDB d "value10"

Full code. You’ll need to use this branch of Bluefin. H does not exist in a published version.

2 Likes

If you stick handlers in State which is an IORef in disguise, then everything breaks horribly once you introduce multiple threads into the equation.

This is why internals of effectful are more complicated. Because it handles this automatically behind the scenes.

3 Likes

Yes, that’s right, although to be precise I’d say “introduce concurrency” rather than “introduce multiple threads” (not that it really weakens your argument) because Bluefin already uses threads for some functionality (such as connectCoroutines) but the usage is synchronized, not concurrent, thus there is no problem.

We’ll see how big a problem this is in practice. If it becomes a problem then I may have to move to an effectful-style implementation where the mutable state is stored in Eff, and can thus be cloned when spawning a new thread. However, I am hopeful that I will discover new concurrency patterns that don’t require cloning all state, because that may be wasteful, especially when there are a lot of States in scope when dealing with graph traversals and such.

1 Like

Thank you for converting the example into bluefin! Indeed, I think this corresponds well with the original code. It doesn’t seem like any ad-hoc patterns specialized for the case are being used; it looks generic. Regarding hookLoggingLocallyForAnyEffect, I’ve come to think that perhaps it might be possible to handle it well by using something like a type class for the data types of compound effects.

For the record, here’s how to use it (I haven’t tested it because passthrough wasn’t available in effectful-2.5, but typechecks except for the passthrough part, so it should work):

-- > main
-- [DummyDB.InsertDB] value1
-- [DummyDB.InsertDB] value2
-- [INFO] Effect executed: InsertDB value2
-- [DummyDB.InsertDB] value3
-- [INFO] Effect executed: InsertDB value3
-- [DummyDB.InsertDB] value4
main :: IO ()
main = runEff . runLog . runDummyDB $ do
    insertDB "value1"
    hookLoggingLocallyForAnyEffect @DB do
        insertDB "value2"
        insertDB "value3"
    insertDB "value4"

class ShowEffect e where
    showEffect :: e m a -> String

instance ShowEffect DB where
    showEffect (InsertDB x) = "InsertDB " <> x

hookLoggingLocallyForAnyEffect ::
    forall e es a.
    (e :> es, Log :> es, DispatchOf e ~ 'Dynamic, ShowEffect e) =>
    Eff es a ->
    Eff es a
hookLoggingLocallyForAnyEffect = interpose @e \env e -> do
    r <- passthrough env e
    log $ "Effect executed: " <> showEffect e
    pure r

That’s really helpful. Thanks!

1 Like

I wonder what other effects are like that, so far examples are logging and tracing. For me, those could come built-in with Eff itself. I really don’t see much value in having this type Log :> es => Eff es () compared to Eff es (). Looking at the 23-effect function, I’d throw structured concurrency to the pile as well. Why would I care if a function spawns threads if they can’t escape its scope? Those are innocent effects that don’t help me understand what a function is doing and what important things it is messing with. Then Eff could provide concurrency primitives that are safe with regard to this built-in functionality. Making other effects safe would be up to the users, they created them, so let them take care of it.

This is a problem for a general purpose effects library, as folks want different loggers and tracers, but as a basis for building applications, I think it would be just fine.

I’ve added this litmus test to the test suite.

I really don’t see much value in having this type Log :> es => Eff es () compared to Eff es ()

I think it depends exactly what Log does. Given that forall es. Eff es r can be converted to r (via runPureEff) if Log is present but not tracked in the types then it had really better be pretty benign. If it’s as benign as Debug.Trace then that’s fine, of course, but then there’s not a lot of point to it at all: you may as well be using Debug.Trace. If it’s logging to files or network connections then that’s much more dubious. In such a case I’d rather have it tracked in the type.