module Control.Comonad (
Comonad(..)
, liftW
, wfix
, cfix
, (=>=)
, (=<=)
, (<<=)
, (=>>)
, ComonadApply(..)
, (<@@>)
, liftW2
, liftW3
, Cokleisli(..)
, Functor(..)
, (<$>)
, ($>)
) where
import Control.Applicative
import Control.Arrow
import Control.Category
import Control.Monad (ap)
import Control.Monad.Instances
import Control.Monad.Trans.Identity
import Data.Functor.Identity
import Data.List.NonEmpty hiding (map)
import Data.Semigroup hiding (Product)
import Data.Tree
import Prelude hiding (id, (.))
import Control.Monad.Fix
import Data.Typeable
infixl 4 <@, @>, <@@>, <@>, $>
infixl 1 =>>
infixr 1 <<=, =<=, =>=
class Functor w => Comonad w where
extract :: w a -> a
duplicate :: w a -> w (w a)
duplicate = extend id
extend :: (w a -> b) -> w a -> w b
extend f = fmap f . duplicate
instance Comonad ((,)e) where
duplicate p = (fst p, p)
extract = snd
instance Monoid m => Comonad ((->)m) where
duplicate f m = f . mappend m
extract f = f mempty
instance Comonad Identity where
duplicate = Identity
extract = runIdentity
instance Comonad w => Comonad (IdentityT w) where
extend f (IdentityT m) = IdentityT (extend (f . IdentityT) m)
extract = extract . runIdentityT
instance Comonad Tree where
duplicate w@(Node _ as) = Node w (map duplicate as)
extract (Node a _) = a
instance Comonad NonEmpty where
extend f w@ ~(_ :| aas) = f w :| case aas of
[] -> []
(a:as) -> toList (extend f (a :| as))
extract ~(a :| _) = a
class Comonad w => ComonadApply w where
(<@>) :: w (a -> b) -> w a -> w b
(@>) :: w a -> w b -> w b
a @> b = const id <$> a <@> b
(<@) :: w a -> w b -> w a
a <@ b = const <$> a <@> b
instance Semigroup m => ComonadApply ((,)m) where
(m, f) <@> (n, a) = (m <> n, f a)
(m, a) <@ (n, _) = (m <> n, a)
(m, _) @> (n, b) = (m <> n, b)
instance ComonadApply NonEmpty where
(<@>) = ap
instance Monoid m => ComonadApply ((->)m) where
(<@>) = (<*>)
(<@ ) = (<* )
( @>) = ( *>)
instance ComonadApply Identity where
(<@>) = (<*>)
(<@ ) = (<* )
( @>) = ( *>)
instance ComonadApply w => ComonadApply (IdentityT w) where
IdentityT wa <@> IdentityT wb = IdentityT (wa <@> wb)
instance ComonadApply Tree where
(<@>) = (<*>)
(<@ ) = (<* )
( @>) = ( *>)
liftW :: Comonad w => (a -> b) -> w a -> w b
liftW f = extend (f . extract)
wfix :: Comonad w => w (w a -> a) -> a
wfix w = extract w (extend wfix w)
cfix :: Comonad w => (w a -> a) -> w a
cfix f = fix (extend f)
(=>>) :: Comonad w => w a -> (w a -> b) -> w b
(=>>) = flip extend
(<<=) :: Comonad w => (w a -> b) -> w a -> w b
(<<=) = extend
(=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> c
f =<= g = f . extend g
(=>=) :: Comonad w => (w a -> b) -> (w b -> c) -> w a -> c
f =>= g = g . extend f
(<@@>) :: ComonadApply w => w a -> w (a -> b) -> w b
(<@@>) = liftW2 (flip id)
liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c
liftW2 f a b = f <$> a <@> b
liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d
liftW3 f a b c = f <$> a <@> b <@> c
newtype Cokleisli w a b = Cokleisli { runCokleisli :: w a -> b }
#ifdef __GLASGOW_HASKELL__
instance Typeable1 w => Typeable2 (Cokleisli w) where
typeOf2 twab = mkTyConApp cokleisliTyCon [typeOf1 (wa twab)]
where wa :: Cokleisli w a b -> w a
wa = undefined
#endif
cokleisliTyCon :: TyCon
#if MIN_VERSION_base(4,4,0)
cokleisliTyCon = mkTyCon3 "comonad" "Control.Comonad" "Cokleisli"
#else
cokleisliTyCon = mkTyCon "Control.Comonad.Cokleisli"
#endif
instance Comonad w => Category (Cokleisli w) where
id = Cokleisli extract
Cokleisli f . Cokleisli g = Cokleisli (f =<= g)
instance Comonad w => Arrow (Cokleisli w) where
arr f = Cokleisli (f . extract)
first f = f *** id
second f = id *** f
Cokleisli f *** Cokleisli g = Cokleisli (f . fmap fst &&& g . fmap snd)
Cokleisli f &&& Cokleisli g = Cokleisli (f &&& g)
instance Comonad w => ArrowApply (Cokleisli w) where
app = Cokleisli $ \w -> runCokleisli (fst (extract w)) (snd <$> w)
instance Comonad w => ArrowChoice (Cokleisli w) where
left = leftApp
instance ComonadApply w => ArrowLoop (Cokleisli w) where
loop (Cokleisli f) = Cokleisli (fst . wfix . extend f') where
f' wa wb = f ((,) <$> wa <@> (snd <$> wb))
instance Functor (Cokleisli w a) where
fmap f (Cokleisli g) = Cokleisli (f . g)
instance Applicative (Cokleisli w a) where
pure = Cokleisli . const
Cokleisli f <*> Cokleisli a = Cokleisli (\w -> (f w) (a w))
instance Monad (Cokleisli w a) where
return = Cokleisli . const
Cokleisli k >>= f = Cokleisli $ \w -> runCokleisli (f (k w)) w
($>) :: Functor f => f a -> b -> f b
($>) = flip (<$)