module Control.Arrow.Mix.Category ((:~>), (:~~>), Along, AlMonad(..), (~>>=), AlFunctor(..), (:$~)(..)) where
import Prelude hiding (id, (.))
import Control.Arrow
import Control.Category
import Control.Arrow.Mix.Utilities
type f :~> g = forall i o. f i o -> g i o
infixr 0 :~>
type f :~~> g = forall i o. (i -> o) -> f i o -> g i o
infixr 0 :~~>
type Along f input output i o = f (input, i) (output, o)
class AlMonad m where
alRet :: Arrow b => b :~> m b
alLift :: (Arrow b, Arrow c) => (Along b i1 o1 :~~> Along (m c) i2 o2) -> (m b i1 o1 -> m c i2 o2)
(~>>=) :: (AlMonad m, Arrow b, Arrow c) => m b i1 o1 -> (Along b i1 o1 :~> Along (m c) i2 o2) -> m c i2 o2
m ~>>= h = alLift (const h) m
infixl 1 ~>>=
class AlFunctor f where
alMap :: (Arrow b, Arrow c) => (Along b i1 o1 :~> Along c i2 o2) -> (f b i1 o1 -> f c i2 o2)
type Strike a b = b
newtype (f :$~ a) input output = Apply {runApply :: a input output `Strike` f a input output} deriving AlMonad
infixl 0 :$~
instance AlMonad m => AlFunctor ((:$~) m) where
alMap h m = m ~>>= \b -> alRet $ h b
instance (AlMonad m, Arrow a) => Category (m :$~ a) where
id = alRet id
m2 . m1 = m1 ~>>= \a1 -> m2 ~>>= \a2 -> alRet $ a1 ->> a2
instance (AlMonad m, Arrow a) => Arrow (m :$~ a) where
arr = alRet . arr
first m = m ~>>= \a -> alRet $ arrTwist $ first a
instance (AlMonad m, ArrowLoop a) => ArrowLoop (m :$~ a) where
loop m = m ~>>= \a -> alRet $ loop $ arrTwist a
instance (AlMonad m, ArrowChoice a) => ArrowChoice (m :$~ a) where
left = alLift $ \t a -> alRet $ arrUnpack $ a +++ arr (second t)