module Control.Arrow.MonadExample where import Control.Arrow.Monad ((>>>=), listen, ) import Control.Arrow.Let ((<<<&), ) import qualified Data.HList as HL import qualified Control.Arrow.Let as CAL import Control.Arrow (Arrow, (&&&), (<<<), (<<^), (^>>), ) import Control.Category (id, ) import Prelude hiding (id, ) mix :: Arrow arrow => arrow (a,a) a mix = undefined delay :: Arrow arrow => arrow a a delay = undefined lowpass :: Arrow arrow => arrow a a lowpass = undefined exampleCombinators, exampleBind, exampleLet, exampleCase :: Arrow arrow => arrow a a exampleCombinators = mix <<< id &&& delay <<< lowpass exampleBind = (\x -> HL.hCons x HL.hNil) ^>> ((HL.hHead ^>> lowpass) >>>= \x -> mix <<< listen x &&& (delay <<< listen x)) exampleLet = let x :: Arrow arrow => arrow (a,()) a x = lowpass <<^ fst in ((mix <<< CAL.ref x &&& (delay <<< CAL.ref x)) <<<& x) <<^ (\i -> (i,())) exampleCase = case lowpass <<^ fst of x -> ((mix <<< CAL.ref x &&& (delay <<< CAL.ref x)) <<<& x) <<^ (\i -> (i,()))