{-# OPTIONS -fglasgow-exts #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Comonad.Parameterized -- Copyright : (C) 2008 Edward Kmett -- License : BSD-style (see the file LICENSE) -- -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : portable -- ---------------------------------------------------------------------------- module Control.Comonad.Parameterized ( module Control.Bifunctor.Biff , module Control.Functor.Pointed.Parameterized , module Control.Comonad , PComonad(..) , pcoaugment ) where import Control.Arrow ((&&&)) import Control.Comonad import Control.Bifunctor.Fix import Control.Bifunctor.Biff import Control.Functor.Pointed.Parameterized import Control.Morphism.Ana class PCopointed f => PComonad f where pextend :: (f b c -> a) -> f b c -> f a c {- Parameterized comonad laws: > pextend pextract = id > pextract . pextend g = g > pextend (g . pextend j) = pextend g . pextend j > pextract . second g = pextract > second g . pextend (j . second g) = pextend j . second g -} {-# RULES "pextend pextract" pextend pextract = id "pextract . pextend g" forall g. pextract . pextend g = g "pextract . bimap id g" forall g. pextract . bimap id g = pextract "bimap _ _ . pextract" forall j g. bimap id g . pextend (j . bimap id g) = pextend j . bimap id g #-} pcoaugment :: PComonad f => ((FixB f a -> f b (FixB f a)) -> FixB f b) -> (FixB f a -> b) -> FixB f b pcoaugment g k = g (pextend (k . InB) . outB) instance PCopointed f => Copointed (FixB f) where extract = pextract . outB instance PComonad f => Comonad (FixB f) where extend k w = pcoaugment (flip biana w) k instance Functor f => PCopointed (BiffB (,) Identity f) where pextract = runIdentity . fst . runBiffB instance Functor f => PComonad (BiffB (,) Identity f) where pextend f = BiffB . (Identity . f &&& snd . runBiffB)