What is a higher-order effect?

Thanks @ocharles, this was very enlightening! Having thought about this I now understand a lot more about many things.

The short response is: yes, I see why these “dynamic” effects are useful, and yes, Bluefin can do them. See the code below, and the comment about main for the sample trace output.


To elaborate on the utility of dynamic effects, the point is that we want to be able to do this

doWork :: Trace :> es => Eff es ()
doWork = inSpan "doWork" do
  jobs <- getJobs
  ...

getJobs :: Database :> es => Eff es Jobs -- No `Trace` here at all!
getJobs = runQuery fetchJobsQuery

that is, define getJobs without reference to Trace, yet define the handler to create a new span, like

runDatabase :: (IOE :> es, Trace :> es) => Eff (Database : es) a -> Eff es a
runDatabase = interpret_ \case
  RunQuery q ->
    inSpan "runQuery" do
       liftIO (performQueryIO q)

and have the "runQuery" span nest beneath the "doWork" span. (You’ll see the Bluefin implementation achieves this.) This particular example was what made it all click into place for me, so thank you very much!


To elaborate on the implementation in Bluefin, what’s going on is that the reader effect is actually a mutable state (local mutates it on enter and restores it on exit), but given that local is the only thing that mutates the state we have the nice property that these two are always the same:

do
  r1 <- ask
  r2 <- ask
  pure (r1, r2)

do
  r1 <- ask
  pure (r1, r1)

So, in the Bluefin version below I implement Reader using State (i.e. mutable state). This is actually what effectful does too! local from Effectful.Reader.Static uses localStaticRep which modifies Eff's Env in a bracket (actually inlineBracket) that restores it afterwards. That’s the same as my Bluefin version.

This implementation scheme is what @arybczak suggested, with the caveat that “what if you then add forkIO to the equation”? Well, that would be bad. The IORef underlying the State would be accessed by multiple threads and it would go wrong. That’s already a problem for Bluefin though. One mitigation would be to take an effectful-style approach and track all mutable states in Eff. Then they can be cloned when we enter new threads. I don’t know if I’ll do that or just detect when withRunInIO is being used to launch a new thread and abort at run time (like effectful does with the SeqUnlift strategy). That must be pretty inefficient with a lot of states in scope, so I think I’d probably rather just come up with safe native Bluefin concurrency patterns, if that’s practical. We shall see.

EDIT: By the way, this shows that my intuition about not understanding the use case of this feature, and my intuition about Bluefin not being able to support it, were both completely wrong. I got bamboozled because I didn’t understand the importance of it being implemented by mutation under the hood.

Preamble
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE DerivingStrategies #-}
{-# OPTIONS_GHC -Wall #-}

import Bluefin.Compound
  ( Handle,
    makeOp,
    mapHandle,
    useImplIn,
    useImplUnder,
  )
import Bluefin.Eff
  ( Eff,
    bracket,
    runEff,
    (:&),
    (:>),
  )
import Bluefin.IO (IOE, effIO)
import Bluefin.State (State, evalState, get, put)
import Bluefin.Stream
  ( Stream,
    forEach,
    yield,
  )
import Data.List ()
import Prelude hiding (span)

newtype Reader r e = MkReader (State r e)
  deriving newtype (Handle)

runReader ::
  r ->
  (forall e. Reader r e -> Eff (e :& es) a) ->
  Eff es a
runReader r k = evalState r (k . MkReader)

ask :: (e :> es) => Reader r e -> Eff es r
ask (MkReader st) = get st

local ::
  (e1 :> es) =>
  Reader r e1 ->
  (r -> r) ->
  Eff es a ->
  Eff es a
local (MkReader st) f k = do
  orig <- get st
  bracket
    (put st (f orig))
    (\() -> put st orig)
    (\() -> k)

data Query r = MkQuery [r]

type Job = String

fetchJobsQuery :: Query Job
fetchJobsQuery = MkQuery ["Job 1", "Job 2", "Job 3"]

performQueryIO :: Query a -> IO [a]
performQueryIO (MkQuery as) = pure as
-- > main
-- doWork
--   runQuery
--     A trace inside runQuery
--   The jobs were
--     ["Job 1","Job 2","Job 3"]
main :: IO ()
main = runEff $ \io -> do
  runTrace io $ \tr -> do
    runDatabase tr io $ \db -> do
      doWork tr db

data Database es = MkDatabase
  { runQueryImpl ::
      forall e a.
      Query a ->
      Eff (e :& es) [a]
  }

instance Handle Database where
  mapHandle db =
    MkDatabase
      { runQueryImpl = \q ->
          useImplUnder (runQueryImpl db q)
      }

runDatabase ::
  (e1 :> es, e2 :> es) =>
  Trace e1 ->
  IOE e2 ->
  (forall e. Database e -> Eff (e :& es) a) ->
  Eff es a
runDatabase tr io k =
  useImplIn
    k
    MkDatabase
      { runQueryImpl =
          \q -> do
            inSpan tr "runQuery" $ do
              trace tr "A trace inside runQuery"
              effIO io (performQueryIO q)
      }

runQuery :: (e :> es) => Database e -> Query a -> Eff es [a]
runQuery db q = makeOp (runQueryImpl (mapHandle db) q)

data Trace e
  = MkTrace (Reader Int e) (Stream String e)

runTrace ::
  (e1 :> es) =>
  IOE e1 ->
  (forall e. Trace e -> Eff (e :& es) r) ->
  Eff es r
runTrace io k = runReader 0 $ \re -> do
  forEach
    ( \stream -> do
        useImplIn k (MkTrace (mapHandle re) (mapHandle stream))
    )
    (\line -> effIO io (putStrLn line))

trace :: (e :> es) => Trace e -> String -> Eff es ()
trace (MkTrace re stream) msg = do
  n <- ask re
  yield stream (replicate (2 * n) ' ' <> msg)

inSpan ::
  (e1 :> es) =>
  Trace e1 ->
  String ->
  Eff es a ->
  Eff es a
inSpan tr@(MkTrace re _) span k = do
  trace tr span
  local re (+ 1) k

doWork ::
  (e1 :> es, e2 :> es) =>
  Trace e1 ->
  Database e2 ->
  Eff es ()
doWork tr db = inSpan tr "doWork" $ do
  jobs <- getJobs db
  inSpan tr "The jobs were" $ do
    trace tr (show jobs)

-- No `Trace` here at all!
getJobs :: (e :> es) => Database e -> Eff es [Job]
getJobs db = runQuery db fetchJobsQuery
4 Likes