functor-combinators-0.1.1.1: Tools for functor combinator-based program design

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Freer.Church

Contents

Description

The church-encoded Freer Monad. Basically provides the free monad in a way that is compatible with HFunctor and Interpret. We also have the "semigroup" version Free1, which is the free Bind.

The module also provides a version of :.: (or Compose), Comp, in a way that is compatible with HBifunctor and the related typeclasses.

Synopsis

Free

newtype Free f a Source #

A Free f is f enhanced with "sequential binding" capabilities. It allows you to sequence multiple fs one after the other, and also to determine "what f to sequence" based on the result of the computation so far.

Essentially, you can think of this as "giving f a Monad instance", with all that that entails (return, >>=, etc.).

Lift f into it with inject :: f a -> Free f a. When you finally want to "use" it, you can interpret it into any monadic context:

interpret
    :: Monad g
    => (forall x. f x -> g x)
    -> Free f a
    -> g a

Structurally, this is equivalent to many "nested" f's. A value of type Free f a is either:

  • a
  • f a
  • f (f a)
  • f (f (f a))
  • .. etc.

Under the hood, this is the Church-encoded Freer monad. It's Free, or F, but in a way that is compatible with HFunctor and Interpret.

Constructors

Free 

Fields

  • runFree :: forall r. (a -> r) -> (forall s. f s -> (s -> r) -> r) -> r
     
Instances
Interpret Free Source #

A free Monad

Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C Free :: (Type -> Type) -> Constraint Source #

Methods

retract :: C Free f => Free f ~> f Source #

interpret :: C Free g => (f ~> g) -> Free f ~> g Source #

FreeOf Monad Free Source # 
Instance details

Defined in Data.HFunctor.Final

MonadFree f (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

wrap :: f (Free f a) -> Free f a #

Monad (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

return :: a -> Free f a #

fail :: String -> Free f a #

Functor (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

Applicative (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

pure :: a -> Free f a #

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

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

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

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

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

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

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

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

null :: Free f a -> Bool #

length :: Free f a -> Int #

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

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

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

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

(Functor f, Eq1 f) => Eq1 (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

(Functor f, Ord1 f) => Ord1 (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

(Functor f, Read1 f) => Read1 (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

(Functor f, Show1 f) => Show1 (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

Apply (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

(<.>) :: Free f (a -> b) -> Free f a -> Free f b #

(.>) :: Free f a -> Free f b -> Free f b #

(<.) :: Free f a -> Free f b -> Free f a #

liftF2 :: (a -> b -> c) -> Free f a -> Free f b -> Free f c #

Pointed (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

point :: a -> Free f a #

Bind (Free f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

join :: Free f (Free f a) -> Free f a #

HBind Free Source # 
Instance details

Defined in Data.HFunctor

Methods

hbind :: (f ~> Free g) -> Free f ~> Free g Source #

hjoin :: Free (Free f) ~> Free f Source #

Inject Free Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> Free f Source #

HFunctor Free Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Free f ~> Free g Source #

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

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

max :: Free f a -> Free f a -> Free f a #

min :: Free f a -> Free f a -> Free f a #

(Functor f, Read1 f, Read a) => Read (Free f a) Source #

Read in terms of pure and wrap.

Instance details

Defined in Control.Monad.Freer.Church

Methods

readsPrec :: Int -> ReadS (Free f a) #

readList :: ReadS [Free f a] #

readPrec :: ReadPrec (Free f a) #

readListPrec :: ReadPrec [Free f a] #

(Functor f, Show1 f, Show a) => Show (Free f a) Source #

Show in terms of pure and wrap.

Instance details

Defined in Control.Monad.Freer.Church

Methods

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

show :: Free f a -> String #

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

type C Free Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C Free = Monad

reFree :: (MonadFree f m, Functor f) => Free f a -> m a Source #

Convert a Free f into any instance of MonadFree f.

Interpretation

liftFree :: f ~> Free f Source #

Lift an f into Free f, so you can use it as a Monad.

This is inject.

interpretFree :: Monad g => (f ~> g) -> Free f ~> g Source #

Interpret a Free f into a context g, provided that g has a Monad instance.

This is interpret.

retractFree :: Monad f => Free f ~> f Source #

Extract the fs back "out" of a Free f, utilizing its Monad instance.

This is retract.

hoistFree :: (f ~> g) -> Free f ~> Free g Source #

Swap out the underlying functor over a Free. This preserves all of the structure of the Free.

Folding

foldFree Source #

Arguments

:: Functor f 
=> (a -> r)

handle pure

-> (f r -> r)

handle wrap

-> Free f a 
-> r 

Recursively fold down a Free by handling the pure case and the nested/wrapped case.

This is a catamorphism.

This requires Functor f; see foldFree' and foldFreeC for a version that doesn't require Functor f.

foldFree' :: (a -> r) -> (forall s. f s -> (s -> r) -> r) -> Free f a -> r Source #

A version of foldFree that doesn't require Functor f, by taking a RankN folding function. This is essentially a flipped runFree.

foldFreeC Source #

Arguments

:: (a -> r)

handle pure

-> (Coyoneda f r -> r)

handle wrap

-> Free f a 
-> r 

A version of foldFree that doesn't require Functor f, by folding over a Coyoneda instead.

Free1

newtype Free1 f a Source #

The Free Bind. Imbues any functor f with a Bind instance.

Conceptually, this is "Free without pure". That is, while normally Free f a is an a, a f a, a f (f a), etc., a Free1 f a is an f a, f (f a), f (f (f a)), etc. It's a Free with "at least one layer of f", excluding the a case.

It can be useful as the semigroup formed by :.: (functor composition): Sometimes we want an f :.: f, or an f :.: f :.: f, or an f :.: f :.: f :.: f...just as long as we have at least one f.

Constructors

Free1 

Fields

  • runFree1 :: forall r. (forall s. f s -> (s -> a) -> r) -> (forall s. f s -> (s -> r) -> r) -> r
     

Bundled Patterns

pattern DoneF1 :: Functor f => f a -> Free1 f a

Constructor matching on the case that a Free1 f consists of just a single un-nested f. Used as a part of the Show and Read instances.

pattern MoreF1 :: Functor f => f (Free1 f a) -> Free1 f a

Constructor matching on the case that a Free1 f is a nested f (Free1 f a). Used as a part of the Show and Read instances.

As a constructor, this is equivalent to wrap.

Instances
Interpret Free1 Source #

A free Bind

Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C Free1 :: (Type -> Type) -> Constraint Source #

Methods

retract :: C Free1 f => Free1 f ~> f Source #

interpret :: C Free1 g => (f ~> g) -> Free1 f ~> g Source #

FreeOf Bind Free1 Source # 
Instance details

Defined in Data.HFunctor.Final

Functor (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

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

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

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

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

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

null :: Free1 f a -> Bool #

length :: Free1 f a -> Int #

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

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

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

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

(Functor f, Eq1 f) => Eq1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

(Functor f, Ord1 f) => Ord1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

(Functor f, Read1 f) => Read1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

(Functor f, Show1 f) => Show1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

Foldable1 f => Foldable1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

fold1 :: Semigroup m => Free1 f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Free1 f a -> m #

toNonEmpty :: Free1 f a -> NonEmpty a #

Apply (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

(<.>) :: Free1 f (a -> b) -> Free1 f a -> Free1 f b #

(.>) :: Free1 f a -> Free1 f b -> Free1 f b #

(<.) :: Free1 f a -> Free1 f b -> Free1 f a #

liftF2 :: (a -> b -> c) -> Free1 f a -> Free1 f b -> Free1 f c #

Traversable1 f => Traversable1 (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Free1 f a -> f0 (Free1 f b) #

sequence1 :: Apply f0 => Free1 f (f0 b) -> f0 (Free1 f b) #

Bind (Free1 f) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

join :: Free1 f (Free1 f a) -> Free1 f a #

HBind Free1 Source # 
Instance details

Defined in Data.HFunctor

Methods

hbind :: (f ~> Free1 g) -> Free1 f ~> Free1 g Source #

hjoin :: Free1 (Free1 f) ~> Free1 f Source #

Inject Free1 Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> Free1 f Source #

HFunctor Free1 Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Free1 f ~> Free1 g Source #

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

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

max :: Free1 f a -> Free1 f a -> Free1 f a #

min :: Free1 f a -> Free1 f a -> Free1 f a #

(Functor f, Read1 f, Read a) => Read (Free1 f a) Source #

Read in terms of DoneF1 and MoreF1.

Instance details

Defined in Control.Monad.Freer.Church

(Functor f, Show1 f, Show a) => Show (Free1 f a) Source #

Show in terms of DoneF1 and MoreF1.

Instance details

Defined in Control.Monad.Freer.Church

Methods

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

show :: Free1 f a -> String #

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

type C Free1 Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C Free1 = Bind

reFree1 :: (MonadFree f m, Functor f) => Free1 f a -> m a Source #

Convert a Free1 f into any instance of MonadFree f.

toFree :: Free1 f ~> Free f Source #

Free1 f is a special subset of Free f that consists of at least one nested f. This converts it back into the "bigger" type.

See free1Comp for a version that preserves the "one nested layer" property.

Interpretation

liftFree1 :: f ~> Free1 f Source #

Inject an f into a Free1 f

interpretFree1 :: Bind g => (f ~> g) -> Free1 f ~> g Source #

Interpret the Free1 f in some context g, provided that g has a Bind instance. Since we always have at least one f, we will always have at least one g, so we do not need a full Monad constraint.

retractFree1 :: Bind f => Free1 f ~> f Source #

Retract the f out of a Free1 f, as long as the f implements Bind. Since we always have at least one f, we do not need a full Monad constraint.

hoistFree1 :: (f ~> g) -> Free1 f ~> Free1 g Source #

Map the underlying functor under a Free1.

Conversion

free1Comp :: Free1 f ~> Comp f (Free f) Source #

Because a Free1 f is just a Free f with at least one nested layer of f, this function converts it back into the one-nested-f format.

matchFree1 :: forall f. Functor f => Free1 f ~> (f :+: Comp f (Free1 f)) Source #

A Free1 f is either a single un-nested f, or a f nested with another Free1 f. This decides which is the case.

Folding

foldFree1 Source #

Arguments

:: Functor f 
=> (f a -> r)

handle DoneF1.

-> (f r -> r)

handle MoreF1.

-> Free1 f a 
-> r 

Recursively fold down a Free1 by handling the single f case and the nested/wrapped case.

This is a catamorphism.

This requires Functor f; see foldFree' and foldFreeC for a version that doesn't require Functor f.

foldFree1' :: (forall s. f s -> (s -> a) -> r) -> (forall s. f s -> (s -> r) -> r) -> Free1 f a -> r Source #

A version of foldFree1 that doesn't require Functor f, by taking a RankN folding function. This is essentially a flipped runFree.

foldFree1C :: (Coyoneda f a -> r) -> (Coyoneda f r -> r) -> Free1 f a -> r Source #

A version of foldFree1 that doesn't require Functor f, by folding over a Coyoneda instead.

Comp

data Comp f g a Source #

Functor composition. Comp f g a is equivalent to f (g a), and the Comp pattern synonym is a way of getting the f (g a) in a Comp f g a.

For example, Maybe (IO Bool) is Comp Maybe IO Bool.

This is mostly useful for its typeclass instances: in particular, Functor, Applicative, HBifunctor, and Monoidal.

This is essentially a version of :.: and Compose that allows for an HBifunctor instance.

It is slightly less performant. Using comp . unComp every once in a while will concretize a Comp value (if you have Functor f) and remove some indirection if you have a lot of chained operations.

The "free monoid" over Comp is Free, and the "free semigroup" over Comp is Free1.

Constructors

(f x) :>>= (x -> g a) 

Bundled Patterns

pattern Comp :: Functor f => f (g a) -> Comp f g a

Pattern match on and construct a Comp f g a as if it were f (g a).

Instances
Semigroupoidal Comp Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type SF Comp :: (Type -> Type) -> Type -> Type Source #

Methods

appendSF :: Comp (SF Comp f) (SF Comp f) ~> SF Comp f Source #

matchSF :: Functor f => SF Comp f ~> (f :+: Comp f (SF Comp f)) Source #

consSF :: Comp f (SF Comp f) ~> SF Comp f Source #

toSF :: Comp f f ~> SF Comp f Source #

biretract :: CS Comp f => Comp f f ~> f Source #

binterpret :: CS Comp h => (f ~> h) -> (g ~> h) -> Comp f g ~> h Source #

Associative Comp Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Comp f (Comp g h) <~> Comp (Comp f g) h Source #

Monoidal Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF Comp :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: Comp (MF Comp f) (MF Comp f) ~> MF Comp f Source #

splitSF :: SF Comp f ~> Comp f (MF Comp f) Source #

splittingMF :: MF Comp f <~> (I Comp :+: Comp f (MF Comp f)) Source #

toMF :: Comp f f ~> MF Comp f Source #

fromSF :: SF Comp f ~> MF Comp f Source #

pureT :: CM Comp f => I Comp ~> f Source #

upgradeC :: CM Comp f => proxy f -> (CS Comp f -> r) -> r Source #

Tensor Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I Comp :: Type -> Type Source #

Methods

intro1 :: f ~> Comp f (I Comp) Source #

intro2 :: g ~> Comp (I Comp) g Source #

elim1 :: Functor f => Comp f (I Comp) ~> f Source #

elim2 :: Functor g => Comp (I Comp) g ~> g Source #

Applicative f => Inject (Comp f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f0 ~> Comp f f0 Source #

HFunctor (Comp f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f0 ~> g) -> Comp f f0 ~> Comp f g Source #

HBifunctor Comp Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hleft :: (f ~> j) -> Comp f g ~> Comp j g Source #

hright :: (g ~> k) -> Comp f g ~> Comp f k Source #

hbimap :: (f ~> j) -> (g ~> k) -> Comp f g ~> Comp j k Source #

Functor g => Functor (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

fmap :: (a -> b) -> Comp f g a -> Comp f g b #

(<$) :: a -> Comp f g b -> Comp f g a #

(Applicative f, Applicative g) => Applicative (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

pure :: a -> Comp f g a #

(<*>) :: Comp f g (a -> b) -> Comp f g a -> Comp f g b #

liftA2 :: (a -> b -> c) -> Comp f g a -> Comp f g b -> Comp f g c #

(*>) :: Comp f g a -> Comp f g b -> Comp f g b #

(<*) :: Comp f g a -> Comp f g b -> Comp f g a #

(Foldable f, Foldable g) => Foldable (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

fold :: Monoid m => Comp f g m -> m #

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

foldr :: (a -> b -> b) -> b -> Comp f g a -> b #

foldr' :: (a -> b -> b) -> b -> Comp f g a -> b #

foldl :: (b -> a -> b) -> b -> Comp f g a -> b #

foldl' :: (b -> a -> b) -> b -> Comp f g a -> b #

foldr1 :: (a -> a -> a) -> Comp f g a -> a #

foldl1 :: (a -> a -> a) -> Comp f g a -> a #

toList :: Comp f g a -> [a] #

null :: Comp f g a -> Bool #

length :: Comp f g a -> Int #

elem :: Eq a => a -> Comp f g a -> Bool #

maximum :: Ord a => Comp f g a -> a #

minimum :: Ord a => Comp f g a -> a #

sum :: Num a => Comp f g a -> a #

product :: Num a => Comp f g a -> a #

(Traversable f, Traversable g) => Traversable (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

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

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

(Alternative f, Alternative g) => Alternative (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

empty :: Comp f g a #

(<|>) :: Comp f g a -> Comp f g a -> Comp f g a #

some :: Comp f g a -> Comp f g [a] #

many :: Comp f g a -> Comp f g [a] #

(Functor f, Eq1 f, Eq1 g) => Eq1 (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

liftEq :: (a -> b -> Bool) -> Comp f g a -> Comp f g b -> Bool #

(Functor f, Ord1 f, Ord1 g) => Ord1 (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

liftCompare :: (a -> b -> Ordering) -> Comp f g a -> Comp f g b -> Ordering #

(Functor f, Read1 f, Read1 g) => Read1 (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Comp f g a] #

(Functor f, Show1 f, Show1 g) => Show1 (Comp f g) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

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

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

(Functor f, Eq1 f, Eq1 g, Eq a) => Eq (Comp f g a) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

(==) :: Comp f g a -> Comp f g a -> Bool #

(/=) :: Comp f g a -> Comp f g a -> Bool #

(Functor f, Ord1 f, Ord1 g, Ord a) => Ord (Comp f g a) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

compare :: Comp f g a -> Comp f g a -> Ordering #

(<) :: Comp f g a -> Comp f g a -> Bool #

(<=) :: Comp f g a -> Comp f g a -> Bool #

(>) :: Comp f g a -> Comp f g a -> Bool #

(>=) :: Comp f g a -> Comp f g a -> Bool #

max :: Comp f g a -> Comp f g a -> Comp f g a #

min :: Comp f g a -> Comp f g a -> Comp f g a #

(Functor f, Read1 f, Read1 g, Read a) => Read (Comp f g a) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

readsPrec :: Int -> ReadS (Comp f g a) #

readList :: ReadS [Comp f g a] #

readPrec :: ReadPrec (Comp f g a) #

readListPrec :: ReadPrec [Comp f g a] #

(Functor f, Show1 f, Show1 g, Show a) => Show (Comp f g a) Source # 
Instance details

Defined in Control.Monad.Freer.Church

Methods

showsPrec :: Int -> Comp f g a -> ShowS #

show :: Comp f g a -> String #

showList :: [Comp f g a] -> ShowS #

type SF Comp Source # 
Instance details

Defined in Data.HBifunctor.Associative

type SF Comp = Free1
type MF Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

type MF Comp = Free
type I Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

type I Comp = Identity

comp :: f (g a) -> Comp f g a Source #

"Smart constructor" for Comp that doesn't require Functor f.