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 i_input = evalState (runKleisli al i_input) s execTest :: Test input output -> input -> IO output execTest t = runKleisli $ unMix $ alMap (const $ 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
- liftImpure :: (ArrowChoice a, ArrowLoop a, Arrow b) => a input output -> (a :+ b) input output
- liftPure :: (Arrow a, Arrow b) => b input output -> (a :+ b) input output
- unMix :: Arrow a => (a :+ (->)) :~> a
- unMix' :: Arrow a => (a :+ a) :~> a
- type :+ a b = Mix a :$~ b
- module Control.Arrow.Mix.Category
- module Control.Arrow.Mix.Utilities
Documentation
liftImpure :: (ArrowChoice a, ArrowLoop a, Arrow b) => a input output -> (a :+ b) input outputSource
We can lift impure arrows
liftPure :: (Arrow a, Arrow b) => b input output -> (a :+ b) input outputSource
Pure arrows can be lifted too
unMix :: 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 alongMap
), we can reduce the type a :+ (->)
to a
.
type :+ a b = Mix a :$~ bSource
a :+ b
is an arrow incapsulating both a
and b
effects. It's functorial (and even monadic) in b
.
module Control.Arrow.Mix.Category
module Control.Arrow.Mix.Utilities