| Safe Haskell | None |
|---|
Control.Arrow.Mix
Description
We try to mix effects of two completely unrelated arrows a and b, where b is considered pure, and a — impure. Probably the most common use case would be a = Kleisli IO. We perform all the pure calculations first, and do the impure ones later.
Usage example:
newtype Test input output = Test {runTest :: (Kleisli IO :+ Kleisli (State String)) input output}
deriving (Category, Arrow, ArrowChoice, ArrowLoop)
runStateMorphism :: s -> Kleisli (State s) :~> (->)
runStateMorphism s al input = evalState (runKleisli al input) s
execTest :: Test input output -> input -> IO output
execTest t = runKleisli $ unPlus $ alMap (runStateMorphism "") $ runTest t
rd = Test {runTest = liftImpure $ Kleisli $ const getLine}
wr = Test {runTest = liftImpure $ Kleisli putStrLn}
gt = Test {runTest = liftPure $ Kleisli $ const get}
pt = Test {runTest = liftPure $ Kleisli put}
test =
proc () ->
do line <- rd -< () -- effect from IO
pt -< line -- effect from State
line' <- gt -< () -- effect from State
wr -< line' -- effect from IO
- module Control.Arrow.Mix.Category
- data (a :+ b) input output
- liftImpure :: (ArrowChoice a, ArrowLoop a, Arrow b) => a :~> (a :+ b)
- liftPure :: (Arrow a, Arrow b) => b :~> (a :+ b)
- unPlus :: Arrow a => (a :+ (->)) :~> a
- unPlus' :: Arrow a => (a :+ a) :~> a
- plusTwist :: (Arrow a, AlFunctor f, Arrow c) => (a :+ f c) :~> f (a :+ c)
- plusAssoc :: (Arrow a, Arrow b, Arrow c) => (a :+ (b :+ c)) :~> ((a :+ b) :+ c)
- plusCommute :: (Arrow a, ArrowChoice b, ArrowLoop b) => (a :+ b) :~> (b :+ a)
Documentation
module Control.Arrow.Mix.Category
data (a :+ b) input output Source
a :+ b is an arrow incapsulating both a and b effects. It's functorial (and even monadic) in b.
liftImpure :: (ArrowChoice a, ArrowLoop a, Arrow b) => a :~> (a :+ b)Source
We can lift impure arrows
unPlus :: Arrow a => (a :+ (->)) :~> aSource
We need some way to extract the real computation from this :+; fortunately, if we manage to reduce the pure arrow to a function (using alMap), we can reduce the type a :+ (->) to a.
unPlus' :: Arrow a => (a :+ a) :~> aSource
If, for some reason, the "pure" arrow is, in fact, as impure as the "impure" one, we still can extract the real computation.
plusTwist :: (Arrow a, AlFunctor f, Arrow c) => (a :+ f c) :~> f (a :+ c)Source
(:+) is right commutative-associative: a :+ (b :+ c) and b :+ (a :+ c) can be reduced to one another with plusTwist function
plusAssoc :: (Arrow a, Arrow b, Arrow c) => (a :+ (b :+ c)) :~> ((a :+ b) :+ c)Source
(:+) is also associative
plusCommute :: (Arrow a, ArrowChoice b, ArrowLoop b) => (a :+ b) :~> (b :+ a)Source
this function is experimental - no idea about how this would interact with other arrow combinators and functions defined in this module