module
Control.Arrow.Machine.Types
where
import qualified Control.Category as Cat
import Data.Monoid (Monoid(..))
import Data.Profunctor (Profunctor, dimap)
import Control.Arrow.Operations (ArrowReader(..))
import Control.Arrow.Transformer.Reader (runReader, ArrowAddReader(..))
import Control.Arrow
data Phase = Feed | Sweep | Suspend deriving (Eq, Show)
instance
Monoid Phase
where
mempty = Sweep
mappend Feed _ = Feed
mappend _ Feed = Feed
mappend Suspend _ = Suspend
mappend _ Suspend = Suspend
mappend Sweep Sweep = Sweep
type StepType a b c = a (Phase, b) (Phase, c, ProcessA a b c)
data ProcessA a b c = ProcessA {
step :: StepType a b c
}
fit :: (Arrow a, Arrow a') =>
(forall p q. a p q -> a' p q) ->
ProcessA a b c -> ProcessA a' b c
fit f (ProcessA af) = ProcessA $ f af >>> arr mod
where
mod (ph, y, next) = (ph, y, fit f next)
instance
Arrow a => Profunctor (ProcessA a)
where
dimap f g pa = ProcessA $ dimapStep f g (step pa)
dimapStep :: Arrow a =>
(b->c)->(d->e)->
StepType a c d -> StepType a b e
dimapStep f g stp = proc (ph, x) ->
do
(ph', y, pa') <- stp -< (ph, f x)
returnA -< (ph', g y, dimap f g pa')
instance
ArrowApply a => Cat.Category (ProcessA a)
where
id = ProcessA (arrStep id)
g . f = ProcessA $ compositeStep (step f) (step g)
instance
ArrowApply a => Arrow (ProcessA a)
where
arr = ProcessA . arrStep
first pa = ProcessA $ proc (ph, (x, d)) ->
do
(ph', y, pa') <- step pa -< (ph, x)
returnA -< (ph' `mappend` Suspend, (y, d), first pa')
pa *** pb = ProcessA $ parStep (step pa) (step pb)
parStep f g = proc (ph, (x1, x2)) ->
do
(ph1, y1, pa') <- f -< (ph, x1)
(ph2, y2, pb') <- g -< (ph, x2)
returnA -< (ph1 `mappend` ph2, (y1, y2), pa' *** pb')
arrStep :: ArrowApply a => (b->c) -> StepType a b c
arrStep f = proc (ph, x) ->
returnA -< (ph `mappend` Suspend, f x, ProcessA $ arrStep f)
compositeStep :: ArrowApply a =>
StepType a b d -> StepType a d c -> StepType a b c
compositeStep f g = proc (ph, x) -> compositeStep' ph f g -<< (ph, x)
compositeStep' :: ArrowApply a =>
Phase ->
StepType a b d -> StepType a d c -> StepType a b c
compositeStep' Sweep f g = proc (_, x) ->
do
(ph1, r1, pa') <- f -< (Suspend, x)
(ph2, r2, pb') <- g -<< (Sweep, r1)
cont ph2 x -<< (r2, pa', pb')
where
cont Feed x = arr $ \(r, pa, pb) -> (Feed, r, pa >>> pb)
cont Sweep x = arr $ \(r, pa, pb) -> (Sweep, r, pa >>> pb)
cont Suspend x = proc (_, pa, pb) ->
do
(ph1, r1, pa') <- step pa -<< (Sweep, x)
(ph2, r2, pb') <- step pb -<< (ph1, r1)
returnA -< (ph2, r2, pa' >>> pb')
compositeStep' ph f g = proc (_, x) ->
do
(ph1, r1, pa') <- f -< (ph, x)
(ph2, r2, pb') <- g -<< (ph1, r1)
returnA -< (ph2, r2, pa' >>> pb')
instance
ArrowApply a => ArrowChoice (ProcessA a)
where
left pa@(ProcessA a) = ProcessA $ proc (ph, eth) -> go ph eth -<< ()
where
go ph (Left x) = proc _ ->
do
(ph', y, pa') <- a -< (ph, x)
returnA -< (ph', Left y, left pa')
go ph (Right d) = proc _ ->
returnA -< (ph `mappend` Suspend, Right d, left pa)
instance
(ArrowApply a, ArrowLoop a) => ArrowLoop (ProcessA a)
where
loop pa = ProcessA $ proc (ph, x) -> loop $ go ph -<< x
where
go ph = proc (x, d) ->
do
(ph', (y, d'), pa') <- step pa -< (ph, (x, d))
returnA -< ((ph', y, loop pa'), d')
instance
(ArrowApply a, ArrowReader r a) =>
ArrowReader r (ProcessA a)
where
readState = ProcessA $ proc (ph, dm) ->
do
r <- readState -< dm
returnA -< (ph `mappend` Suspend, r, readState)
newReader pa = ProcessA $ proc (ph, (e, r)) ->
do
(ph', y, pa') <- newReader (step pa) -< ((ph, e), r)
returnA -< (ph', y, newReader pa')
instance
(ArrowApply a, ArrowApply a', ArrowAddReader r a a') =>
ArrowAddReader r (ProcessA a) (ProcessA a')
where
liftReader pa = ProcessA $ proc (ph, x) ->
do
(ph', y, pa') <- (| liftReader (step pa -< (ph, x)) |)
returnA -< (ph', y, liftReader pa)
elimReader pra =
ProcessA $ arr pre >>> elimReader (step pra) >>> arr post
where
pre (ph, (x, r)) = ((ph, x), r)
post (ph, x, pra') = (ph, x, elimReader pra')