hs-functors-0.1.4.0: Functors from products of Haskell and its dual to Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Comonad.Cofree

Documentation

data Cofree f a Source #

Constructors

Cofree 

Fields

Instances
Alternative f => Monad (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

(>>=) :: Cofree f a -> (a -> Cofree f b) -> Cofree f b #

(>>) :: Cofree f a -> Cofree f b -> Cofree f b #

return :: a -> Cofree f a #

fail :: String -> Cofree f a #

Functor f => Functor (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

fmap :: (a -> b) -> Cofree f a -> Cofree f b #

(<$) :: a -> Cofree f b -> Cofree f a #

Alternative f => Applicative (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

pure :: a -> Cofree f a #

(<*>) :: Cofree f (a -> b) -> Cofree f a -> Cofree f b #

liftA2 :: (a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c #

(*>) :: Cofree f a -> Cofree f b -> Cofree f b #

(<*) :: Cofree f a -> Cofree f b -> Cofree f a #

Foldable f => Foldable (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

fold :: Monoid m => Cofree f m -> m #

foldMap :: Monoid m => (a -> m) -> Cofree f a -> m #

foldr :: (a -> b -> b) -> b -> Cofree f a -> b #

foldr' :: (a -> b -> b) -> b -> Cofree f a -> b #

foldl :: (b -> a -> b) -> b -> Cofree f a -> b #

foldl' :: (b -> a -> b) -> b -> Cofree f a -> b #

foldr1 :: (a -> a -> a) -> Cofree f a -> a #

foldl1 :: (a -> a -> a) -> Cofree f a -> a #

toList :: Cofree f a -> [a] #

null :: Cofree f a -> Bool #

length :: Cofree f a -> Int #

elem :: Eq a => a -> Cofree f a -> Bool #

maximum :: Ord a => Cofree f a -> a #

minimum :: Ord a => Cofree f a -> a #

sum :: Num a => Cofree f a -> a #

product :: Num a => Cofree f a -> a #

Traversable f => Traversable (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Cofree f a -> f0 (Cofree f b) #

sequenceA :: Applicative f0 => Cofree f (f0 a) -> f0 (Cofree f a) #

mapM :: Monad m => (a -> m b) -> Cofree f a -> m (Cofree f b) #

sequence :: Monad m => Cofree f (m a) -> m (Cofree f a) #

Eq1 f => Eq1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftEq :: (a -> b -> Bool) -> Cofree f a -> Cofree f b -> Bool #

Ord1 f => Ord1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftCompare :: (a -> b -> Ordering) -> Cofree f a -> Cofree f b -> Ordering #

Read1 f => Read1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Cofree f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Cofree f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Cofree f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Cofree f a] #

Show1 f => Show1 (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Cofree f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Cofree f a] -> ShowS #

Functor f => Comonad (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

copure :: Cofree f a -> a Source #

cut :: Cofree f a -> Cofree f (Cofree f a) Source #

(<<=) :: (Cofree f a -> b) -> Cofree f a -> Cofree f b Source #

Cotraversable f => Cotraversable (Cofree f) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

collect :: Functor g => (a -> Cofree f b) -> g a -> Cofree f (g b) Source #

cosequence :: Functor g => g (Cofree f a) -> Cofree f (g a) Source #

cotraverse :: Functor g => (g a -> b) -> g (Cofree f a) -> Cofree f b Source #

(Eq1 f, Eq a) => Eq (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

(==) :: Cofree f a -> Cofree f a -> Bool #

(/=) :: Cofree f a -> Cofree f a -> Bool #

(Ord1 f, Ord a) => Ord (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

compare :: Cofree f a -> Cofree f a -> Ordering #

(<) :: Cofree f a -> Cofree f a -> Bool #

(<=) :: Cofree f a -> Cofree f a -> Bool #

(>) :: Cofree f a -> Cofree f a -> Bool #

(>=) :: Cofree f a -> Cofree f a -> Bool #

max :: Cofree f a -> Cofree f a -> Cofree f a #

min :: Cofree f a -> Cofree f a -> Cofree f a #

(Read1 f, Read a) => Read (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

(Show1 f, Show a) => Show (Cofree f a) Source # 
Instance details

Defined in Control.Comonad.Cofree

Methods

showsPrec :: Int -> Cofree f a -> ShowS #

show :: Cofree f a -> String #

showList :: [Cofree f a] -> ShowS #

raise :: Comonad ɯ => ɯ a -> Cofree ɯ a Source #

lower :: Functor ɯ => Cofree ɯ a -> ɯ a Source #

coiter :: Functor f => (a -> f a) -> a -> Cofree f a Source #

coiterW :: (Comonad ɯ, Functor f) => (ɯ a -> f (ɯ a)) -> ɯ a -> Cofree f a Source #

unfold :: Functor f => (a -> (b, f a)) -> a -> Cofree f b Source #

unfoldM :: (Traversable f, Monad m) => (a -> m (b, f a)) -> a -> m (Cofree f b) Source #

unfoldW :: (Cotraversable f, Comonad ɯ) => (ɯ a -> (b, f a)) -> ɯ a -> Cofree f b Source #

map :: Functor f => (forall a. f a -> g a) -> Cofree f a -> Cofree g a Source #