functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

FMonad.FFree

Description

Free FMonad

Synopsis

Documentation

data FFree ff g x Source #

The free FMonad for a FFunctor ff.

Constructors

FPure (g x) 
FFree (ff (FFree ff g) x) 

Instances

Instances details
FFunctor ff => FFunctor (FFree ff) Source # 
Instance details

Defined in FMonad.FFree

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> FFree ff g x -> FFree ff h x Source #

FFunctor ff => FMonad (FFree ff) Source # 
Instance details

Defined in FMonad.FFree

Methods

fpure :: forall (g :: Type -> Type). Functor g => g ~> FFree ff g Source #

fbind :: forall (g :: Type -> Type) (h :: Type -> Type) a. (Functor g, Functor h) => (g ~> FFree ff h) -> FFree ff g a -> FFree ff h a Source #

FStrong ff => FStrong (FFree ff) Source # 
Instance details

Defined in FMonad.FFree

Methods

fstrength :: forall (g :: Type -> Type) (h :: Type -> Type). Functor g => Day (FFree ff g) h ~> FFree ff (Day g h) Source #

mapCurried :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => Curried g h ~> Curried (FFree ff g) (FFree ff h) Source #

(Foldable g, Foldable (ff (FFree ff g))) => Foldable (FFree ff g) Source # 
Instance details

Defined in FMonad.FFree

Methods

fold :: Monoid m => FFree ff g m -> m #

foldMap :: Monoid m => (a -> m) -> FFree ff g a -> m #

foldMap' :: Monoid m => (a -> m) -> FFree ff g a -> m #

foldr :: (a -> b -> b) -> b -> FFree ff g a -> b #

foldr' :: (a -> b -> b) -> b -> FFree ff g a -> b #

foldl :: (b -> a -> b) -> b -> FFree ff g a -> b #

foldl' :: (b -> a -> b) -> b -> FFree ff g a -> b #

foldr1 :: (a -> a -> a) -> FFree ff g a -> a #

foldl1 :: (a -> a -> a) -> FFree ff g a -> a #

toList :: FFree ff g a -> [a] #

null :: FFree ff g a -> Bool #

length :: FFree ff g a -> Int #

elem :: Eq a => a -> FFree ff g a -> Bool #

maximum :: Ord a => FFree ff g a -> a #

minimum :: Ord a => FFree ff g a -> a #

sum :: Num a => FFree ff g a -> a #

product :: Num a => FFree ff g a -> a #

(Traversable g, Traversable (ff (FFree ff g))) => Traversable (FFree ff g) Source # 
Instance details

Defined in FMonad.FFree

Methods

traverse :: Applicative f => (a -> f b) -> FFree ff g a -> f (FFree ff g b) #

sequenceA :: Applicative f => FFree ff g (f a) -> f (FFree ff g a) #

mapM :: Monad m => (a -> m b) -> FFree ff g a -> m (FFree ff g b) #

sequence :: Monad m => FFree ff g (m a) -> m (FFree ff g a) #

(FStrong ff, Applicative g) => Applicative (FFree ff g) Source # 
Instance details

Defined in FMonad.FFree

Methods

pure :: a -> FFree ff g a #

(<*>) :: FFree ff g (a -> b) -> FFree ff g a -> FFree ff g b #

liftA2 :: (a -> b -> c) -> FFree ff g a -> FFree ff g b -> FFree ff g c #

(*>) :: FFree ff g a -> FFree ff g b -> FFree ff g b #

(<*) :: FFree ff g a -> FFree ff g b -> FFree ff g a #

(Functor g, Functor (ff (FFree ff g))) => Functor (FFree ff g) Source # 
Instance details

Defined in FMonad.FFree

Methods

fmap :: (a -> b) -> FFree ff g a -> FFree ff g b #

(<$) :: a -> FFree ff g b -> FFree ff g a #

(Show (g a), Show (ff (FFree ff g) a)) => Show (FFree ff g a) Source # 
Instance details

Defined in FMonad.FFree

Methods

showsPrec :: Int -> FFree ff g a -> ShowS #

show :: FFree ff g a -> String #

showList :: [FFree ff g a] -> ShowS #

(Eq (g a), Eq (ff (FFree ff g) a)) => Eq (FFree ff g a) Source # 
Instance details

Defined in FMonad.FFree

Methods

(==) :: FFree ff g a -> FFree ff g a -> Bool #

(/=) :: FFree ff g a -> FFree ff g a -> Bool #

(Ord (g a), Ord (ff (FFree ff g) a)) => Ord (FFree ff g a) Source # 
Instance details

Defined in FMonad.FFree

Methods

compare :: FFree ff g a -> FFree ff g a -> Ordering #

(<) :: FFree ff g a -> FFree ff g a -> Bool #

(<=) :: FFree ff g a -> FFree ff g a -> Bool #

(>) :: FFree ff g a -> FFree ff g a -> Bool #

(>=) :: FFree ff g a -> FFree ff g a -> Bool #

max :: FFree ff g a -> FFree ff g a -> FFree ff g a #

min :: FFree ff g a -> FFree ff g a -> FFree ff g a #

fffmap :: forall ff gg h. (FFunctor ff, FFunctor gg, Functor h) => (forall h'. Functor h' => ff h' ~> gg h') -> FFree ff h ~> FFree gg h Source #

iter :: forall ff g. (FFunctor ff, Functor g) => (ff g ~> g) -> FFree ff g ~> g Source #

Iteratively fold a FFree term down, given a way to fold one layer of ff.

foldFFree :: forall ff mm g. (FFunctor ff, FMonad mm, Functor g) => (forall h. Functor h => ff h ~> mm h) -> FFree ff g ~> mm g Source #

Fold a FFree term to another FMonad mm.

retract :: (FMonad ff, Functor g) => FFree ff g ~> ff g Source #

retract = foldFFree id

liftF :: (FFunctor ff, Functor g) => ff g ~> FFree ff g Source #

Lift a single layer of ff into FFree ff