What is a higher-order effect?

I’d been hoping to write this post since you gave your talk, but unfortunately I wasn’t able to find the time. A lot of discourse has happened since, and it’s been very interesting! One of my questions in the talk was about local, and there’s been a lot of fascinating points in this thread about it. Something I wanted to raise was a concrete example of where local is practically useful.

Perhaps the biggest use of it in CircuitHub’s codebase has been for tracing instrumentation, and it’s been so useful I’d consider this functionality indispensable. So without further ado, let’s start looking at some code. We are effectful users, so this example is going to use effectful. First, let’s look at the API of the Trace effect.

data Trace :: Effect

inSpan :: (HasCallStack, Trace :> es) => Text -> Eff es a -> Eff es a

Essentially the Trace effect lets us scope a block of code as belonging to an OpenTelemetry tracing span. Clients can use this to instrument there code, for example

doWork :: Trace :> es => Eff es ()
doWork = inSpan "doWork" do
  ...

But another use of this is to use it from within another effect handler:

data Database :: Effect where
  RunQuery :: Query -> Database m QueryResults

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

This is already quite cool, and let’s us do things like

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

We can run this program with something like:

main :: IO ()
main = runEff $ runTrace $ runDatabase $ doWork

The result of this in now when we call doWork we create a new tracing span "doWork" and then within this span we get a child span "runQuery":

  • doWork
    • runQuery

But when we think about it, this is quite remarkable action at a distance! The Database interpreter knows nothing about doWork creating spans, but somehow everything fits together perfectly.

Even more fascinating is this works even when we split things apart even more:

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

I skipped the implementation of Trace and inSpanat the start, but they work in exactly the same way as Reader and local! The Trace effect is basically a reader effect that has access to the current tracing span (if any), and whenever we call inSpan we lookup the current span and create a new span that is a child of the current span (ala local). We then use local to run the associated block of code with the current span changed to this new parent.

This is really what I wanted to know if bluefin was capable of expressing. It’s this interaction between effects that I find incredibly powerful, and it work out very naturally in effectful. As @michaelpj said, we did have some confusion understanding this at first - we thought that the runQuery method must have had to have the Trace effect itself for this to work - that is, we thought we’d have to have:

data Database :: Effect where
  RunQuery :: Trace :> es => Query -> Database (Eff es) QueryResults

But the real beauty is we don’t have to do this at all - tracing in the interpretation of the Database effect is entirely hidden from users, but if users themselves use tracing it also perfectly interacts with it!

But we do even more with this Reader- like behavior. Another thing that we’ve found really powerful is the ability to capture the current tracing span and then restore it later. This one is a little harder to motivate, but here’s one fairly self-contained example. We have a machine learning inference step. Running the inference is relatively quick, but we also want to archive the inference so we can review it at a later date. This archiving should have tracing spans, and we want to associate this with the inference step, but we don’t actually want to block on archiving - it should happen in the background. Our solution is to have a separate archiving thread that consumes a queue of (InfereneceResult, TracingContext). Whenever we archive an inference, we first reset our context to the given context:

runDetector = reinterpret withSavedInferences \_ -> \case
  Detect image -> do
    inSpan "detect" do
      found <- runInference image

      inferenceResults <- ask @(TQueue PartDetectionInference)
      sourceContext <- getContext
      atomically $
        writeTQueue
          inferenceResults
          Inference
            { sourceImage = image
            , sourceContext
            }

      pure found
  where
    withSavedInferences m = Ki.scoped \ki -> do
      inferenceResults <- atomically $ newTQueue @Inference

      _ <- fork ki do
        forever $ tryAny do
          saveInference =<< atomically (readTQueue inferenceResults)

      runReader inferenceResults m

    saveInference inference = withContext inference.sourceContext $ inSpan "saveInference" do
      ...

Again, if saveInference calls anything that uses Tracing - even if it’s within an effect interpreter like we saw with Database - everything gets associated as expected.

Hopefully that’s given an insight into why, from a practical point of view, one might want this local functionality! What I really like is that I don’t really have to think about how any of this works. I don’t have to think about state or mutation - I just think about how Reader works.

I look forward to hearing if bluefin can do any of this! If this isn’t clear enough, I’m happy to try and put a self-contained effectful example together.

9 Likes