Code Monkey home page Code Monkey logo

eff's Introduction

eff — screaming fast extensible effects for less Build Status Documentation

🚧 This library is currently under construction. 🚧

eff is a work-in-progress implementation of an extensible effect system for Haskell, a general-purpose solution for tracking effects at the type level and handling them in flexible ways. Compared to other effect systems currently available, eff differentiates itself in the following respects:

  • eff is really fast. Built on top of low-level primitives added to the GHC RTS to support capturing slices of the call stack, eff is performant by design. Using a direct implementation of delimited control allows it to be fast without relying on fickle compiler optimizations to eliminate indirection.

    Traditional effect system microbenchmarks fail to capture the performance of real code, as they are so small that GHC often ends up inlining everything. In real programs, GHC compiles most effect-polymorphic code via dictionary passing, not specialization, causing the performance of other effect systems to degrade beyond what microbenchmarks would imply. eff takes care to allow GHC to generate efficient code without the need for whole-program specialization.

  • eff is low-boilerplate and easy to use, even without Template Haskell or any generic programming. eff’s interface is comparable to freer-simple and polysemy, but writing new effect handlers is made even simpler thanks to a small set of highly expressive core operations.

  • eff is expressive, providing support for both first-order/algebraic effects and higher-order/scoped effects, like fused-effects and polysemy (but unlike freer-simple).

  • eff’s semantics is precise and easy to reason about, based on models of delimited control. Other approaches to scoped operations (including those taken in mtl, fused-effects, and polysemy) have behavior that changes depending on handler order, and some combinations can lead to nonsensical results. eff’s semantics is consistent regardless of handler order, and scoped operations compose in predictable ways.

eff in action

To illustrate just how easy it is to define and handle effects in eff, the following code example includes 100% of the code necessary to define a custom FileSystem effect and two handlers, one that runs in IO and another that uses an in-memory virtual file system:

import qualified System.IO as IO
import Prelude hiding (readFile, writeFile)
import Control.Effect

-- -----------------------------------------------------------------------------
-- effect definition

data FileSystem :: Effect where
  ReadFile :: FilePath -> FileSystem m String
  WriteFile :: FilePath -> String -> FileSystem m ()

readFile :: FileSystem :< effs => FilePath -> Eff effs String
readFile = send . ReadFile

writeFile :: FileSystem :< effs => FilePath -> String -> Eff effs ()
writeFile a b = send $ WriteFile a b

-- -----------------------------------------------------------------------------
-- IO handler

runFileSystemIO :: IOE :< effs => Eff (FileSystem ': effs) a -> Eff effs a
runFileSystemIO = interpret \case
  ReadFile path -> liftIO $ IO.readFile path
  WriteFile path contents -> liftIO $ IO.writeFile path contents

-- -----------------------------------------------------------------------------
-- pure handler

runFileSystemPure :: Error String :< effs => Eff (FileSystem ': effs) a -> Eff effs a
runFileSystemPure = lift
  >>> interpret \case
        ReadFile path -> do
          fileSystem <- get
          case lookup path fileSystem of
            Just contents -> pure contents
            Nothing       -> throw ("readFile: no such file " <> path)
        WriteFile path contents -> do
          fileSystem <- get
          -- add the new file and remove an old file with the same name, if it exists
          put ((path, contents) : filter ((/= path) . fst) fileSystem)
  >>> evalState @[(FilePath, String)] []

That’s it. For a thorough explanation of how the above example works, see the eff documentation.

Implementation status

eff is a work in progress, and since it requires changes to the GHC RTS, you cannot use it yet on any released version of GHC. If there is interest, I can try to provide builds of GHC with the necessary changes to use eff, but otherwise you will need to wait for them to be merged into GHC proper before using eff yourself. There is currently an open GHC proposal to add the necessary operations, and the work-in-progress implementation branch is available here.

Looking beyond that, many things are still not yet implemented. More work needs to be done to properly interoperate with IO exceptions, and the set of built-in effects currently provided is very small. However, all the existing functionality works, and it has been designed to support extensions, so I do not anticipate any difficulty supporting them.

This library is also sorely lacking a benchmark suite. I have a small set of microbenchmarks I have been using to test out various scenarios and edge cases of different effect libraries, but they need to be cleaned up and added to this repository, and a set of less synthetic benchmarks are also important to assess real-world performance. If you have a small but non-trivial program where differences in effect system performance are significant, I would be much obliged if you could share it to build a more realistic set of effect system benchmarks.

Acknowledgements, citations, and related work

All code in eff is original in the sense that it was not taken directly from other libraries, but much of it is directly inspired by the existing work of many others. The following is a non-exhaustive list of people and works that have had a significant impact, directly or indirectly, on eff’s design and implementation:

eff's People

Contributors

jackfirth avatar lexi-lambda avatar voidus avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

eff's Issues

Functional dependencies?

Heyo! I apologize in advance that this may end up being silly because I confess that I am still pretty new to most GHC extensions, but I have been racking my brain over the language option docs in the GHC user guide and I can't seem to get anywhere.

TLDR: Is it possible to use functional dependencies in classes like State s m or Reader r m or is that not feasible in the design of this library?

I saw the announcement for this library on reddit and decided to try to use it to do stuff. Here's a basic example that fails to compile without AllowAmbiguousTypes:

{-# LANGUAGE AllowAmbiguousTypes #-}

module Foo where

import Control.Effect.State
import Control.Effect.Writer
import System.Random

addNum :: forall g m. (RandomGen g, State g m, Writer [Int] m) => m ()
addNum = do
    gen <- get @g
    let (num, gen') = randomR @Int @g (0, 100) gen
    put gen'
    tell [num]

If I don't include the pragma, I get the following error:

src/Foo.hs:9:11: error:
    • Could not deduce (RandomGen g0)
      from the context: (RandomGen g, State g m, Writer [Int] m)
        bound by the type signature for:
                   addNum :: forall g (m :: * -> *).
                             (RandomGen g, State g m, Writer [Int] m) =>
                             m ()
        at src/Foo.hs:9:11-70
      The type variable ‘g0’ is ambiguous
    • In the ambiguity check for ‘addNum’
      To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
      In the type signature:
        addNum :: forall g m.
                  (RandomGen g, State g m, Writer [Int] m) => m ()
  |
9 | addNum :: forall g m. (RandomGen g, State g m, Writer [Int] m) => m ()
  | 

which is presumably because GHC has no reason to believe that an arbitrary m () could possibly satisfy the constraints.

Moreover, even with that flag, I need to sprinkle around type applications; otherwise...

src/Foo.hs:11:12: error:
    • Could not deduce (State s0 m) arising from a use of ‘get’
      from the context: (RandomGen g, State g m, Writer [Int] m)
        bound by the type signature for:
                   addNum :: forall g (m :: * -> *).
                             (RandomGen g, State g m, Writer [Int] m) =>
                             m ()
        at src/Foo.hs:9:1-70
      The type variable ‘s0’ is ambiguous
      Relevant bindings include addNum :: m () (bound at src/Foo.hs:10:1)
      These potential instances exist:
        instance Monad m => State s (StateT s m)
          -- Defined in ‘Control.Effect.State’
        ...plus one instance involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block: gen <- get
      In the expression:
        do gen <- get
           let (num, gen') = randomR ... gen
           put gen'
           tell [num]
      In an equation for ‘addNum’:
          addNum
            = do gen <- get
                 let (num, gen') = ...
                 put gen'
                 ....
   |
11 |     gen <- get
   |            ^^^

src/Foo.hs:12:23: error:
    • Could not deduce (Random a0) arising from a use of ‘randomR’
      from the context: (RandomGen g, State g m, Writer [Int] m)
        bound by the type signature for:
                   addNum :: forall g (m :: * -> *).
                             (RandomGen g, State g m, Writer [Int] m) =>
                             m ()
        at src/Foo.hs:9:1-70
      The type variable ‘a0’ is ambiguous
      Relevant bindings include num :: a0 (bound at src/Foo.hs:12:10)
      These potential instances exist:
        instance Random Integer -- Defined in ‘System.Random’
        instance Random Bool -- Defined in ‘System.Random’
        instance Random Char -- Defined in ‘System.Random’
        ...plus four others
        ...plus 29 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In the expression: randomR (0, 100) gen
      In a pattern binding: (num, gen') = randomR (0, 100) gen
      In the expression:
        do gen <- get
           let (num, gen') = randomR ... gen
           put gen'
           tell [num]
   |
12 |     let (num, gen') = randomR (0, 100) gen
   |                       ^^^^^^^^^^^^^^^^^^^^

src/Foo.hs:12:32: error:
    • Could not deduce (Num a0) arising from the literal ‘0’
      from the context: (RandomGen g, State g m, Writer [Int] m)
        bound by the type signature for:
                   addNum :: forall g (m :: * -> *).
                             (RandomGen g, State g m, Writer [Int] m) =>
                             m ()
        at src/Foo.hs:9:1-70
      The type variable ‘a0’ is ambiguous
      Relevant bindings include num :: a0 (bound at src/Foo.hs:12:10)
      These potential instances exist:
        instance Num Integer -- Defined in ‘GHC.Num’
        instance Num Double -- Defined in ‘GHC.Float’
        instance Num Float -- Defined in ‘GHC.Float’
        ...plus two others
        ...plus 39 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In the expression: 0
      In the first argument of ‘randomR’, namely ‘(0, 100)’
      In the expression: randomR (0, 100) gen
   |
12 |     let (num, gen') = randomR (0, 100) gen
   |                                ^

src/Foo.hs:14:5: error:
    • Could not deduce (Writer [a0] m) arising from a use of ‘tell’
      from the context: (RandomGen g, State g m, Writer [Int] m)
        bound by the type signature for:
                   addNum :: forall g (m :: * -> *).
                             (RandomGen g, State g m, Writer [Int] m) =>
                             m ()
        at src/Foo.hs:9:1-70
      The type variable ‘a0’ is ambiguous
      Relevant bindings include
        num :: a0 (bound at src/Foo.hs:12:10)
        addNum :: m () (bound at src/Foo.hs:10:1)
      These potential instances exist:
        two instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block: tell [num]
      In the expression:
        do gen <- get
           let (num, gen') = randomR ... gen
           put gen'
           tell [num]
      In an equation for ‘addNum’:
          addNum
            = do gen <- get
                 let (num, gen') = ...
                 put gen'
                 ....
   |
14 |     tell [num]
   | 

Here's the same thing in mtl; in particular, I no longer need AllowAmbiguousTypes, and I can even get away with leaving out the type applications:

import Control.Monad.State
import Control.Monad.Writer
import System.Random

addNum :: forall g m. (RandomGen g, MonadState g m, MonadWriter [Int] m) => m ()
addNum = do
    gen <- get
    let (num, gen') = randomR (0, 100) gen
    put gen'
    tell [num]

Assuming that I'm just bad at type magic, I asked over at the Haskell discourse if anyone could spot what I was missing. artem's comment pointed me to a possible solution: namely that the State class in eff does not specify a functional dependency m -> s.

To my eye this would make sense; whatever monad we happen to be in should be able to fix the type of state that it's holding. But if I just naively try to add that dependency, eff no longer compiles; specifically, changing this line to class Monad m => State s m | m -> s where yields

src/Control/Effect/State.hs:40:10: error:
    • Illegal instance declaration for ‘State s (EffT t m)’
        The liberal coverage condition fails in class ‘State’
          for functional dependency: ‘m -> s’
        Reason: lhs type ‘EffT t m’ does not determine rhs type ‘s’
        Un-determined variable: s
    • In the instance declaration for ‘State s (EffT t m)’
   |
40 | instance (Monad (t m), Send (State s) t m) => State s (EffT t m) where
   |

Feeling around Internal.hs I also added | m -> eff here and here, and | m -> effs here. Now I get:

src/Control/Effect/Internal.hs:194:10: error:
    • Illegal instance declaration for ‘Handle 'True eff t m’
        The liberal coverage condition fails in class ‘Handle’
          for functional dependency: ‘m -> eff’
        Reason: lhs type ‘m’ does not determine rhs type ‘eff’
        Un-determined variable: eff
    • In the instance declaration for ‘Handle 'True eff t m’
    |
194 | instance eff (t m) => Handle 'True eff t m where
    |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

src/Control/Effect/Internal.hs:198:10: error:
    • Illegal instance declaration for ‘Handle 'False eff t m’
        The liberal coverage condition fails in class ‘Handle’
          for functional dependency: ‘m -> eff’
        Reason: lhs type ‘m’ does not determine rhs type ‘eff’
        Un-determined variable: eff
    • In the instance declaration for ‘Handle 'False eff t m’
    |
198 | instance (MonadTransControl t, eff m) => Handle 'False eff t m where
    |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

src/Control/Effect/Internal.hs:285:10: error:
    • Illegal instance declaration for ‘Can effs m’
        The liberal coverage condition fails in class ‘Can’
          for functional dependency: ‘m -> effs’
        Reason: lhs type ‘m’ does not determine rhs type ‘effs’
        Un-determined variable: effs
    • In the instance declaration for ‘Can effs m’
    |
285 | instance All effs m => Can effs m
    |

At this point I am thoroughly out of my league with type families; my guess is that the solution has to do with type family dependencies but I am not sure what that would look like. Based on comparing the examples in the doc to what I see here, there is too much going on that I don't yet get :(

If functional dependencies are simply not possible, is the use of AllowAmbiguousTypes for this sort of thing unavoidable? Or is there another option I am missing?

Thanks for any advice!!

`unsafeCoerce` derivable from `Coroutine`+`locally`+`abort`

As I was studying @lexi-lambda's comment here, I realized that disappearing handlers through coroutines could be unsafe as-is. After some experimentation, turns out I was right:

import Data.Either
import Control.Effect
import Control.Effect.Coroutine

data SomeAction :: Effect where
  SomeAction :: m () -> SomeAction m a

someAction :: SomeAction :< effs
           => Eff effs ()
           -> Eff effs a
someAction = send . SomeAction

runSomeAction :: b -> Eff (SomeAction ': effs) a -> Eff effs (Either b a)
runSomeAction b = handle (pure . Right) $ \(SomeAction m) ->
  locally m >> abort (Left b)

effUnsafeCoerce :: a -> b
effUnsafeCoerce a = fromLeft @_ @() undefined $ run $ do
  eta <-   runSomeAction a
         $ runCoroutine
         $ app
  interpret (\(SomeAction _) -> undefined) $ case eta of
    Right (Yielded () c) -> undefined <$ runCoroutine (c ())

app :: Eff '[Coroutine () (), SomeAction] a
app = someAction (yield ())
>  effUnsafeCoerce (False :: Bool) :: Int
140208895230160

This, unsurprisingly, still works if you use Error instead of abort directly.

runSomeAction :: b -> Eff (SomeAction ': effs) a -> Eff effs (Either b a)
runSomeAction b =
      lift
  >>> interpret (\(SomeAction m) -> locally m >> liftH (throw b))
  >>> runError

runCoroutine internally uses control0, so the culprit here is a nefarious interaction between control0 + locally + abort.

Question: Will it be possible to define an Async/Concurrency effect?

I'm currently doing research into understanding why it is that certain effects are absent from various effect systems. Of particular importance to me is to be able to use asynchronous operations in my effectful code as many data sources can be used to fetch things concurrently, greatly improving performance. It appears that fused-effects is unable to support this in its current design. Since eff takes a fundamentally different approach with the GHC Primops proposal (great proposal btw), will this re-enable the ability to define asynchronous operations?

Related: are coroutines and asynchronous operations the same thing? I ask because coroutines are explicitly mentioned in the Delimited Continuations proposal as one of the motivating factors. To my uneducated self these seem like the same thing, but it is also tough to tell.

Incorrect semantics for higher-order effects

First-order effect systems like freer-simple can make use of interpreters/effect interception to have pseudo higher-order actions, like handleError and catchError.
Unfortunately, such actions have semantic issues, since they rely on inspecting what effects are used of the target computation or rely on all uses of the relevant effect targeting a top-most effect of the effect stack -- either of which leads to incorrect results if intermediary effects get in the way.

Here's an example of freer-simple:

data SomeEff a where
  SomeAction :: SomeEff String

someAction = send SomeAction

-- returns (Left "not caught")
bad :: Either String String
bad = run $ runError @String $ interpret (\SomeAction -> throwError "not caught") $
  someAction `catchError` \(_ :: String) -> return "caught"
-- doesn't matter if "handleError" is used instead of "catchError"

Note that the exception doesn't get caught here even though both the use of throwError and catchError target the same Error effect. Compare this to polysemy, where the exception does, indeed, get caught.

I can't check this myself because I can't figure out custom compilers with cabal, but from what I've seen, eff uses the same approach as freer-simple for its higher-order effects -- the only difference between freer-simple's handleError and eff's catch is that the interpretation done on-site with handleError is done within the interpreter for catch. In this case, eff should have the same issue. Confirmed by @TheMatten.

Potential type error in Error law

Following our discussion on irc I am still trying to wrap my head around the catch handling in eff.

While looking at the law for catch I wondered if the pure is correct there.

According to this type signature:

catch :: Error e :< effs => Eff (Error e ': effs) a -> (e -> Eff effs a) -> Eff effs a 

I deduce the types catch (throw x) f :: Eff effs a and f x :: Eff effs a, so pure (f x) :: Applicative a1 => a1 (Eff effs a)?

So I think instead of catch (throw x) f ≡ pure (f x) it should just be catch (throw x) f ≡ f x.

Definition of 'interpret' in document is incorrect

Definition of interpret is given as following in the 'Simple effect handlers' section:

interpret f = handle (liftH . f)

However, this must not have type checked since handle requires term of type (a -> Eff effs r) before term of type (forall effs' b. eff :< effs' => eff (Eff effs') b -> Handle eff effs a r effs' b) (which is liftH . f). Therefore I checked definition of interpret in codebase and it was interpret f = handle pure (liftH . f). I think it would be better to remedy this.

Nix setup

It would be great if there was a shell.nix that pulls in the GHC fork required for this library to build properly. Then nix users can simply start developing by executing:

nix-shell
cabal build

If you want, I can set that up. I just need the link to your custom GHC.

Links in the docs point to your local filesystem

Every link that points outside this package points to the local copy on your filesystem instead of for example hackage docs. For example, the link to MonadTransControl here points to file:///Users/alexis/.cabal/store/ghc-8.8.1/mnd-cntrl-1.0.2.3-b06f566f/share/doc/html/Control-Monad-Trans-Control.html#t:MonadTransControl.

This flag might work: https://cabal.readthedocs.io/en/latest/nix-local-build.html#cfg-flag---html-location

If not, just close or ignore the issue, since it's a minor issue and not worth wasting a lot of time on. (And it might be impossible to fix: https://stackoverflow.com/questions/57916341/how-to-instruct-haddock-to-link-to-hackage-documentation-for-hackage-packages)

any future plan?

Hi @lexi-lambda, haven't seen any updates since you put out no-monad-control branch. Just curious what's the future plan on this project. Sorry to ask if you are busy on something else.

`censor` semantics doesn’t agree with mtl

The mtl censor will apply the function on the whole output of the monadic action, while eff applies it on each telled output. This can generate different accumulated values unless f is an endomorphism.

Is this intentional?

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.