| Copyright | Allele Dev 2016 |
|---|---|
| License | BSD-3 |
| Maintainer | allele.dev@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.Monad.Freer.Reader
Description
Composable handler for Reader effects. Handy for encapsulating an environment with immutable state for interpreters.
Using http://okmij.org/ftp/Haskell/extensible/Eff1.hs as a starting point.
Documentation
asks :: (b -> a) -> Eff '[Reader b] a Source #
Request a value from the environment and applys as function
local :: forall e a r. Member (Reader e) r => (e -> e) -> Eff r a -> Eff r a Source #
Locally rebind the value in the dynamic environment This function is like a relay; it is both an admin for Reader requests, and a requestor of them
Example 1: Simple Reader Usage
In this example the Reader monad provides access to variable bindings.
Bindings are a Map of integer variables.
The variable count contains number of variables in the bindings.
You can see how to run a Reader effect and retrieve data from it
with runReader, how to access the Reader data with ask and asks.
import Control.Monad.Freer
import Control.Monad.Freer.Reader
import Data.Map as Map
import Data.Maybe
type Bindings = Map String Int
-- Returns True if the "count" variable contains correct bindings size.
isCountCorrect :: Bindings -> Bool
isCountCorrect bindings = run $ runReader calc_isCountCorrect bindings
-- The Reader effect, which implements this complicated check.
calc_isCountCorrect :: Eff '[Reader Bindings] Bool
calc_isCountCorrect = do
count <- asks (lookupVar "count")
bindings <- (ask :: Eff '[Reader Bindings] Bindings)
return (count == (Map.size bindings))
-- The selector function to use with 'asks'.
-- Returns value of the variable with specified name.
lookupVar :: String -> Bindings -> Int
lookupVar name bindings = fromJust (Map.lookup name bindings)
sampleBindings :: Map.Map String Int
sampleBindings = Map.fromList [("count",3), ("1",1), ("b",2)]
main = do
putStr $ "Count is correct for bindings " ++ (show sampleBindings) ++ ": "
putStrLn $ show (isCountCorrect sampleBindings)Example 2: Modifying Reader Content With local
Shows how to modify Reader content with local.
import Control.Monad.Freer
import Control.Monad.Freer.Reader
import Data.Map as Map
import Data.Maybe
type Bindings = Map String Int
calculateContentLen :: Eff '[Reader String] Int
calculateContentLen = do
content <- (ask :: Eff '[Reader String] String)
return (length content)
-- Calls calculateContentLen after adding a prefix to the Reader content.
calculateModifiedContentLen :: Eff '[Reader String] Int
calculateModifiedContentLen = local ("Prefix " ++) calculateContentLen
main :: IO ()
main = do
let s = "12345";
let modifiedLen = run $ runReader calculateModifiedContentLen s;
let len = run $ runReader calculateContentLen s ;
putStrLn $ "Modified 's' length: " ++ (show modifiedLen)
putStrLn $ "Original 's' length: " ++ (show len)