Library freer-effects
(actively maintained fork of
freer
) is an implementation of
effect system for Haskell, which is based on the work of Oleg Kiselyov et al.:
Much of the implementation is a repackaging and cleaning up of the reference materials provided here.
The key features of Freer are:
- An efficient effect system for Haskell as a library.
- Implementations for several common Haskell monads as effects:
Reader
Writer
State
StateRW
: State in terms of Reader/Writer.Trace
Exception
- Core components for defining your own Effects.
Here's what using Freer looks like:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
module Console where
import Control.Monad.Freer
import Control.Monad.Freer.Internal
import System.Exit hiding (ExitSuccess)
--------------------------------------------------------------------------------
-- Effect Model --
--------------------------------------------------------------------------------
data Console s where
PutStrLn :: String -> Console ()
GetLine :: Console String
ExitSuccess :: Console ()
putStrLn' :: Member Console r => String -> Eff r ()
putStrLn' = send . PutStrLn
getLine' :: Member Console r => Eff r String
getLine' = send GetLine
exitSuccess' :: Member Console r => Eff r ()
exitSuccess' = send ExitSuccess
--------------------------------------------------------------------------------
-- Effectful Interpreter --
--------------------------------------------------------------------------------
runConsole :: Eff '[Console] w -> IO w
runConsole (Val x) = return x
runConsole (E u q) =
case extract u of
PutStrLn msg -> putStrLn msg >> runConsole (qApp q ())
GetLine -> getLine >>= \s -> runConsole (qApp q s)
ExitSuccess -> exitSuccess
--------------------------------------------------------------------------------
-- Pure Interpreter --
--------------------------------------------------------------------------------
runConsolePure :: [String] -> Eff '[Console] w -> [String]
runConsolePure inputs req =
reverse . snd $ run (handleRelayS (inputs, []) (\s _ -> pure s) go req)
where
go :: ([String], [String])
-> Console v
-> (([String], [String]) -> Arr '[] v ([String], [String]))
-> Eff '[] ([String], [String])
go (is, os) (PutStrLn msg) q = q (is, msg : os) ()
go (i:is, os) GetLine q = q (is, os) i
go ([], _ ) GetLine _ = error "Not enough lines"
go (_, os) ExitSuccess _ = pure ([], os)
You already have some mtl
code and
are afraid that combining effects with your current tranformer stack would not
be possible? Package
freer-effects-extra
has some
mtl
-related and other goodies.
Contributions are welcome! Documentation, examples, code, and feedback - they all help.
The easiest way to start contributing is to install stack. Stack can install GHC/Haskell for you, and automates common developer tasks.
The key commands are:
stack setup
– install required version of GHC compilerstack build
– builds project, dependencies are automatically resolvedstack test
– builds project, its tests, and executes the testsstack bench
– builds project, its benchmarks, and executes the benchamksstack ghci
– start a REPL instance with a project modules loadedstack clean
stack haddock
– builds documentation
For more information about stack
tool can be found in its
documentation.
This project is distrubted under a BSD3 license. See the included LICENSE file for more details.
Package freer-effects
started as a fork of
freer authored by Allele Dev.
This package would not be possible without the paper and the reference implementation. In particular:
Data.OpenUnion
maps to OpenUnion51.hsData.FTCQueue
maps to FTCQueue1Control.Monad.Freer*
maps to Eff1.hs
There will be deviations from the source.