eveff: Efficient effect handlers based on evidence translation.

[ control, effect, library, mit ] [ Propose Tags ]

See the Control.Ev.Eff module or README.md for further information


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 1.0.0.0, 1.0.0.1, 1.0.0.2
Change log ChangeLog.md
Dependencies base (>=4.7 && <5), ghc-prim, primitive [details]
License MIT
Copyright (c) 2020, Microsoft Research, Daan Leijen, Ningning Xie
Author Daan Leijen, Ningning Xie
Maintainer xnning@hku.hk;daan@microsoft.com
Category Control, Effect
Home page https://github.com/xnning/eveff#readme
Bug tracker https://github.com/xnning/eveff/issues
Source repo head: git clone https://github.com/xnning/eveff
Uploaded by ningningxie at 2021-07-19T02:21:39Z
Distributions NixOS:1.0.0.2
Downloads 620 total (14 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2021-07-19 [all 1 reports]

Readme for eveff-1.0.0.2

[back to package description]

EvEff: Efficient effect handlers based on Evidence translation

Efficient effect handlers based on evidence translation [1]. The interface and design is described in detail in "Effect Handlers in Haskell, Evidently", Ningning Xie and Daan Leijen, Haskell 2020.

An example of defining and using a Reader effect:

{-# LANGUAGE  TypeOperators, FlexibleContexts, Rank2Types #-}
import Control.Ev.Eff

-- A @Reader@ effect definition with one operation @ask@ of type @()@ to @a@.
data Reader a e ans = Reader{ ask :: Op () a e ans }

greet :: (Reader String :? e) => Eff e String
greet = do s <- perform ask ()
           return ("hello " ++ s)

test :: String
test = runEff $
       handler (Reader{ ask = value "world" }) $  -- @:: Reader String () Int@
       do s <- greet                              -- executes in context @:: Eff (Reader String :* ()) Int@
          return s

Enjoy,
Daan Leijen and Ningning Xie, May 2020.

[1] "Effect Handlers, Evidently", Ningning Xie et al., ICFP 2020 (pdf).