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

Data.HBifunctor

Contents

Description

This module provides an abstraction for "two-argument functor combinators", HBifunctor, as well as some useful combinators.

Synopsis

Documentation

class HBifunctor t where Source #

A HBifunctor is like an HFunctor, but it enhances two different functors instead of just one.

Usually, it enhaces them "together" in some sort of combining way.

This typeclass provides a uniform instance for "swapping out" or "hoisting" the enhanced functors. We can hoist the first one with hleft, the second one with hright, or both at the same time with hbimap.

For example, the f :*: g type gives us "both f and g":

data (f :*: g) a = f a :*: g a

It combines both f and g into a unified structure --- here, it does it by providing both f and g.

The single law is:

hbimap id id == id

This ensures that hleft, hright, and hbimap do not affect the structure that t adds on top of the underlying functors.

Minimal complete definition

hleft, hright | hbimap

Methods

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

Swap out the first transformed functor.

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

Swap out the second transformed functor.

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

Swap out both transformed functors at the same time.

Instances
HBifunctor (Sum :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

hright :: (g ~> k0) -> Sum f g ~> Sum f k0 Source #

hbimap :: (f ~> j) -> (g ~> k0) -> Sum f g ~> Sum j k0 Source #

HBifunctor ((:+:) :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

hright :: (g ~> k0) -> (f :+: g) ~> (f :+: k0) Source #

hbimap :: (f ~> j) -> (g ~> k0) -> (f :+: g) ~> (j :+: k0) Source #

HBifunctor (Product :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

hright :: (g ~> k0) -> Product f g ~> Product f k0 Source #

hbimap :: (f ~> j) -> (g ~> k0) -> Product f g ~> Product j k0 Source #

HBifunctor ((:*:) :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

hright :: (g ~> k0) -> (f :*: g) ~> (f :*: k0) Source #

hbimap :: (f ~> j) -> (g ~> k0) -> (f :*: g) ~> (j :*: k0) Source #

HBifunctor (Joker :: (k2 -> Type) -> (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

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

HBifunctor (LeftF :: (k2 -> Type) -> (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

HBifunctor (RightF :: (k1 -> Type) -> (k2 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

HBifunctor (Void3 :: (k1 -> Type) -> (k2 -> Type) -> k3 -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

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

HBifunctor Day Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

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

HBifunctor These1 Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

hbimap :: (f ~> j) -> (g ~> k) -> These1 f g ~> These1 j k 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 #

newtype WrappedHBifunctor t (f :: k -> Type) (g :: k -> Type) a Source #

Useful newtype to allow us to derive an HFunctor instance from any instance of HBifunctor, using -XDerivingVia.

For example, because we have instance HBifunctor Day, we can write:

deriving via (WrappedHBifunctor Day f) instance HFunctor (Day f)

to give us an automatic HFunctor instance and save us some work.

Constructors

WrapHBifunctor 

Fields

Instances
HBifunctor t => HFunctor (WrappedHBifunctor t f :: (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

Functor (t f g) => Functor (WrappedHBifunctor t f g) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

fmap :: (a -> b) -> WrappedHBifunctor t f g a -> WrappedHBifunctor t f g b #

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

overHBifunctor :: HBifunctor t => (f <~> f') -> (g <~> g') -> t f g <~> t f' g' Source #

Lift two isomorphisms on each side of a bifunctor to become an isomorphism between the two bifunctor applications.

Basically, if f and f' are isomorphic, and g and g' are isomorphic, then t f g is isomorphic to t f' g'.

Simple Instances

newtype LeftF f g a Source #

An HBifunctor that ignores its second input. Like a :+: with no R1/right branch.

This is Joker from Data.Bifunctors.Joker, but given a more sensible name for its purpose.

Constructors

LeftF 

Fields

Instances
HBifunctor (LeftF :: (k2 -> Type) -> (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Defined in Data.HBifunctor

Methods

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

Semigroupoidal (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

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

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

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

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

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

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

Associative (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

Functor f => Bifunctor (LeftF f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> LeftF f a c -> LeftF f b d #

first :: (a -> b) -> LeftF f a c -> LeftF f b c #

second :: (b -> c) -> LeftF f a b -> LeftF f a c #

Traversable f => Bitraversable (LeftF f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> LeftF f a b -> f0 (LeftF f c d) #

Foldable f => Bifoldable (LeftF f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

bifold :: Monoid m => LeftF f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> LeftF f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> LeftF f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> LeftF f a b -> c #

Applicative f => Biapplicative (LeftF f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

bipure :: a -> b -> LeftF f a b #

(<<*>>) :: LeftF f (a -> b) (c -> d) -> LeftF f a c -> LeftF f b d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f0) -> LeftF f a d -> LeftF f b e -> LeftF f c f0 #

(*>>) :: LeftF f a b -> LeftF f c d -> LeftF f c d #

(<<*) :: LeftF f a b -> LeftF f c d -> LeftF f a b #

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

Defined in Data.HBifunctor

Methods

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

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

Foldable f => Foldable (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

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

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

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

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

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

null :: LeftF f g a -> Bool #

length :: LeftF f g a -> Int #

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

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

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

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

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

Traversable f => Traversable (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Eq1 f => Eq1 (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

Ord1 f => Ord1 (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

Read1 f => Read1 (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Show1 f => Show1 (LeftF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

Eq (f a) => Eq (LeftF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

(Typeable g, Typeable a, Typeable f, Typeable k2, Typeable k1, Data (f a)) => Data (LeftF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> LeftF f g a -> c (LeftF f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LeftF f g a) #

toConstr :: LeftF f g a -> Constr #

dataTypeOf :: LeftF f g a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LeftF f g a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LeftF f g a)) #

gmapT :: (forall b. Data b => b -> b) -> LeftF f g a -> LeftF f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftF f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftF f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> LeftF f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftF f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftF f g a -> m (LeftF f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftF f g a -> m (LeftF f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftF f g a -> m (LeftF f g a) #

Ord (f a) => Ord (LeftF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

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

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

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

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

Defined in Data.HBifunctor

Methods

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

readList :: ReadS [LeftF f g a] #

readPrec :: ReadPrec (LeftF f g a) #

readListPrec :: ReadPrec [LeftF f g a] #

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

Defined in Data.HBifunctor

Methods

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

show :: LeftF f g a -> String #

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

Generic (LeftF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Associated Types

type Rep (LeftF f g a) :: Type -> Type #

Methods

from :: LeftF f g a -> Rep (LeftF f g a) x #

to :: Rep (LeftF f g a) x -> LeftF f g a #

type SF (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type SF (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) = (Flagged :: (Type -> Type) -> Type -> Type)
type Rep (LeftF f g a) Source # 
Instance details

Defined in Data.HBifunctor

type Rep (LeftF f g a) = D1 (MetaData "LeftF" "Data.HBifunctor" "functor-combinators-0.1.1.1-B2oyFu2GVTM8ySAuzVPoNk" True) (C1 (MetaCons "LeftF" PrefixI True) (S1 (MetaSel (Just "runLeftF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

newtype RightF f g a Source #

An HBifunctor that ignores its first input. Like a :+: with no L1/left branch.

In its polykinded form (on f), it is essentially a higher-order version of Tagged.

Constructors

RightF 

Fields

Instances
HBifunctor (RightF :: (k1 -> Type) -> (k2 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Defined in Data.HBifunctor

Methods

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

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

Defined in Data.HBifunctor

Methods

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

HBind (RightF f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

hbind :: (f0 ~> RightF f g) -> RightF f f0 ~> RightF f g Source #

hjoin :: RightF f (RightF f f0) ~> RightF f f0 Source #

Inject (RightF f :: (k1 -> Type) -> k1 -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Methods

inject :: f0 ~> RightF f f0 Source #

Semigroupoidal (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

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

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

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

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

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

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

Associative (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

Interpret (RightF f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

Associated Types

type C (RightF f) :: (Type -> Type) -> Constraint Source #

Methods

retract :: C (RightF f) f0 => RightF f f0 ~> f0 Source #

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

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

Defined in Data.HBifunctor

Methods

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

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

Foldable g => Foldable (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

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

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

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

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

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

null :: RightF f g a -> Bool #

length :: RightF f g a -> Int #

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

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

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

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

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

Traversable g => Traversable (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Eq1 g => Eq1 (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

Ord1 g => Ord1 (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

Read1 g => Read1 (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

Show1 g => Show1 (RightF f g) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

Eq (g a) => Eq (RightF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

(Typeable f, Typeable a, Typeable g, Typeable k1, Typeable k2, Data (g a)) => Data (RightF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> RightF f g a -> c (RightF f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RightF f g a) #

toConstr :: RightF f g a -> Constr #

dataTypeOf :: RightF f g a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RightF f g a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RightF f g a)) #

gmapT :: (forall b. Data b => b -> b) -> RightF f g a -> RightF f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RightF f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RightF f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> RightF f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RightF f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RightF f g a -> m (RightF f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RightF f g a -> m (RightF f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RightF f g a -> m (RightF f g a) #

Ord (g a) => Ord (RightF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Methods

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

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

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

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

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

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

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

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

Defined in Data.HBifunctor

Methods

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

readList :: ReadS [RightF f g a] #

readPrec :: ReadPrec (RightF f g a) #

readListPrec :: ReadPrec [RightF f g a] #

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

Defined in Data.HBifunctor

Methods

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

show :: RightF f g a -> String #

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

Generic (RightF f g a) Source # 
Instance details

Defined in Data.HBifunctor

Associated Types

type Rep (RightF f g a) :: Type -> Type #

Methods

from :: RightF f g a -> Rep (RightF f g a) x #

to :: Rep (RightF f g a) x -> RightF f g a #

type SF (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type SF (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) = (Step :: (Type -> Type) -> Type -> Type)
type C (RightF f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor

type C (RightF f :: (Type -> Type) -> Type -> Type) = (Unconstrained :: (Type -> Type) -> Constraint)
type Rep (RightF f g a) Source # 
Instance details

Defined in Data.HBifunctor

type Rep (RightF f g a) = D1 (MetaData "RightF" "Data.HBifunctor" "functor-combinators-0.1.1.1-B2oyFu2GVTM8ySAuzVPoNk" True) (C1 (MetaCons "RightF" PrefixI True) (S1 (MetaSel (Just "runRightF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g a))))