[Haskell-cafe] Algebraic Effects?

Viktor Dukhovni ietf-dane at dukhovni.org
Tue Sep 18 15:49:54 UTC 2018


> On Sep 18, 2018, at 2:06 AM, Alexis King <lexi.lambda at gmail.com> wrote:
> 
>  - The ecosystem of EE libraries is a mess.

Yes, it is rather unclear to me whether exploring any of these is
is worth the effort, if so which, or how to use them given sometimes
scant documentation.

>    There are
>    extensible-effects, freer, freer-effects, freer-simple, and others.
>    As far as I can tell, extensible-effects is based on free monads,
>    and freer and freer-effects are both unmaintained.

I took a quick look at:

  https://hackage.haskell.org/package/extensible-0.4.10.

The author claims good performance:

  https://www.schoolofhaskell.com/user/fumieval/extensible/the-world-s-fastest-extensible-effects-framework

I've not tried any benchmarks or yet any non-trivial code using this library.

The documentation is rather minimal, but I got the below to compile and run:

    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE TypeOperators #-}
    
    module Main where
    
    import Control.Monad.Reader (ask)
    import Control.Monad.State (get, put)
    import Control.Monad.Writer (tell)
    import Control.Monad.IO.Class (liftIO)
    import Data.Monoid (Sum(..))
    
    import Data.Extensible
    import Data.Extensible.Effect.Default
    
    type IOeff = "IO" :> IO
    type KitchenSink a = Eff '[ReaderDef Int, StateDef Int, WriterDef (Sum Int), IOeff] a
    type JustIO a = Eff '[IOeff] a
    type Result a = ((a, Int), Sum Int)
    
    handler :: KitchenSink a -> JustIO (Result a)
    handler = runWriterDef . flip runStateDef 3 . flip runReaderDef 5
    
    main :: IO ()
    main = do
        x <- retractEff $ handler $ do
            liftIO $ putStrLn "running"
            s <- get
            r <- ask
            tell (Sum s)
            tell (Sum $ s + 1)
            put $! s + r
            return $ "magic"
        print x

it outputs:

    running
    (("magic",8),Sum {getSum = 7})

With this library, at least when building effects out of mtl transformers,
the order of the effects in the Eff type declaration has to match in
reverse order the composition of the "runFooDef" functions.  That is,
the types:

	Eff '[ReaderDef r, StateDef s]
and
	Eff '[StateDef s, ReaderDef r]

are not the same.  Perhaps this is a feature?

> 
> My recommendation: if the performance of using EE is acceptable in your
> application AND you are willing to pay the cost of less ecosystem
> support (which in practice means needing to write adapters to mtl style
> libraries and having access to less documentation), I would strongly
> recommend the freer-simple extensible effect library. MASSIVE
> DISCLAIMER: I am the author and maintainer of freer-simple! However, I
> have a few reasons to believe I am not wholly biased:

Thanks.  I'll take a look.  Any comments on similarities to or
differences from the "extensible" package above?

> The distinguishing features of freer-simple are better documentation

Barring major downsides, that's a compelling difference.

> and a dramatically different (and hopefully easier to understand) API for
> defining new effects compared to other extensible effects libraries. For
> details, see the freer-simple module documentation on Hackage here:
> 
>  https://hackage.haskell.org/package/freer-simple/docs/Control-Monad-Freer.html
> 
> If you have any further questions, I’m happy to answer them, but this
> email is long enough already! Hopefully it isn’t too overwhelming.

Much appreciated.  Still trying to figure out whether to look into this
further.  My project runs a concurrent computation for many hours, allocating
and freeing terabytes of memory over its lifetime:

  5,019,533,368,664 bytes allocated in the heap
    162,945,132,824 bytes copied during GC
         73,229,680 bytes maximum residency (3421 sample(s))
          4,150,592 bytes maximum slop
                356 MB total memory in use (83 MB lost due to fragmentation)

One concern for me is whether using Effects is likely to cause more allocations
and work for the GC, or is the memory pressure about the same?

-- 
	Viktor.



More information about the Haskell-Cafe mailing list