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

Data.Functor.Bicompose

Synopsis

Documentation

newtype Bicompose f g h a Source #

Both-side composition of Monad.

If both of f and g are Monad, Bicompose f g is an instance of FMonad in a similar way Compose and Precompose are.

Constructors

Bicompose 

Fields

Instances

Instances details
(Comonad f, Comonad g) => FComonad (Bicompose f g) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

fextract :: forall (g0 :: Type -> Type). Functor g0 => Bicompose f g g0 ~> g0 Source #

fextend :: forall (g0 :: Type -> Type) (h :: Type -> Type). (Functor g0, Functor h) => (Bicompose f g g0 ~> h) -> Bicompose f g g0 ~> Bicompose f g h Source #

(Functor f, Functor g) => FFunctor (Bicompose f g) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

ffmap :: forall (g0 :: Type -> Type) (h :: Type -> Type) x. (Functor g0, Functor h) => (g0 ~> h) -> Bicompose f g g0 x -> Bicompose f g h x Source #

(Monad f, Monad g) => FMonad (Bicompose f g) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

fpure :: forall (g0 :: Type -> Type). Functor g0 => g0 ~> Bicompose f g g0 Source #

fbind :: forall (g0 :: Type -> Type) (h :: Type -> Type) a. (Functor g0, Functor h) => (g0 ~> Bicompose f g h) -> Bicompose f g g0 a -> Bicompose f g h a Source #

(Functor f, Functor f') => FStrong (Bicompose f f') Source # 
Instance details

Defined in FStrong

Methods

fstrength :: forall (g :: Type -> Type) (h :: Type -> Type). Functor g => Day (Bicompose f f' g) h ~> Bicompose f f' (Day g h) Source #

mapCurried :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => Curried g h ~> Curried (Bicompose f f' g) (Bicompose f f' h) Source #

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

Defined in Data.Functor.Bicompose

Methods

fold :: Monoid m => Bicompose f g h m -> m #

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

foldMap' :: Monoid m => (a -> m) -> Bicompose f g h a -> m #

foldr :: (a -> b -> b) -> b -> Bicompose f g h a -> b #

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

foldl :: (b -> a -> b) -> b -> Bicompose f g h a -> b #

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

foldr1 :: (a -> a -> a) -> Bicompose f g h a -> a #

foldl1 :: (a -> a -> a) -> Bicompose f g h a -> a #

toList :: Bicompose f g h a -> [a] #

null :: Bicompose f g h a -> Bool #

length :: Bicompose f g h a -> Int #

elem :: Eq a => a -> Bicompose f g h a -> Bool #

maximum :: Ord a => Bicompose f g h a -> a #

minimum :: Ord a => Bicompose f g h a -> a #

sum :: Num a => Bicompose f g h a -> a #

product :: Num a => Bicompose f g h a -> a #

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

Defined in Data.Functor.Bicompose

Methods

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

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

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

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

(Alternative f, Applicative g, Applicative h) => Alternative (Bicompose f g h) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

empty :: Bicompose f g h a #

(<|>) :: Bicompose f g h a -> Bicompose f g h a -> Bicompose f g h a #

some :: Bicompose f g h a -> Bicompose f g h [a] #

many :: Bicompose f g h a -> Bicompose f g h [a] #

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

Defined in Data.Functor.Bicompose

Methods

pure :: a -> Bicompose f g h a #

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

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

(*>) :: Bicompose f g h a -> Bicompose f g h b -> Bicompose f g h b #

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

(Functor f, Functor h, Functor g) => Functor (Bicompose f g h) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

fmap :: (a -> b) -> Bicompose f g h a -> Bicompose f g h b #

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

Read (f (h (g a))) => Read (Bicompose f g h a) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

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

readList :: ReadS [Bicompose f g h a] #

readPrec :: ReadPrec (Bicompose f g h a) #

readListPrec :: ReadPrec [Bicompose f g h a] #

Show (f (h (g a))) => Show (Bicompose f g h a) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

showsPrec :: Int -> Bicompose f g h a -> ShowS #

show :: Bicompose f g h a -> String #

showList :: [Bicompose f g h a] -> ShowS #

(Eq1 f, Eq1 g, Eq1 h, Eq a) => Eq (Bicompose f g h a) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

(==) :: Bicompose f g h a -> Bicompose f g h a -> Bool #

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

(Ord1 f, Ord1 g, Ord1 h, Ord a) => Ord (Bicompose f g h a) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

compare :: Bicompose f g h a -> Bicompose f g h a -> Ordering #

(<) :: Bicompose f g h a -> Bicompose f g h a -> Bool #

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

(>) :: Bicompose f g h a -> Bicompose f g h a -> Bool #

(>=) :: Bicompose f g h a -> Bicompose f g h a -> Bool #

max :: Bicompose f g h a -> Bicompose f g h a -> Bicompose f g h a #

min :: Bicompose f g h a -> Bicompose f g h a -> Bicompose f g h a #