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.