| Copyright | (c) Justin Le 2019 | 
|---|---|
| License | BSD3 | 
| Maintainer | justin@jle.im | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.HBifunctor
Contents
Description
This module provides an abstraction for "two-argument functor
 combinators", HBifunctor, as well as some useful combinators.
Synopsis
- class HBifunctor (t :: (k -> Type) -> (k -> Type) -> k -> Type) where
- newtype WrappedHBifunctor t (f :: k -> Type) (g :: k -> Type) (a :: k) = WrapHBifunctor {- unwrapHBifunctor :: t f g a
 
- overHBifunctor :: HBifunctor t => (f <~> f') -> (g <~> g') -> t f g <~> t f' g'
- newtype LeftF f g a = LeftF {- runLeftF :: f a
 
- newtype RightF f g a = RightF {- runRightF :: g a
 
Documentation
class HBifunctor (t :: (k -> Type) -> (k -> Type) -> k -> Type) 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:
hbimapidid == id
This ensures that hleft, hright, and hbimap do not affect the
 structure that t adds on top of the underlying functors.
Methods
hleft :: (f ~> j) -> t f g ~> t j g Source #
Swap out the first transformed functor.
hright :: (g ~> l) -> t f g ~> t f l Source #
Swap out the second transformed functor.
hbimap :: (f ~> j) -> (g ~> l) -> t f g ~> t j l Source #
Swap out both transformed functors at the same time.
Instances
| HBifunctor Night Source # | Since: 0.3.0.0 | 
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Night f g ~> Night j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Night f g ~> Night f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Night f g ~> Night j l Source # | |
| HBifunctor Night Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Night f g ~> Night j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Night f g ~> Night f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Night f g ~> Night j l Source # | |
| HBifunctor Day Source # | Since: 0.3.0.0 | 
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Day f g ~> Day j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Day f g ~> Day f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Day f g ~> Day j l Source # | |
| HBifunctor Day Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Day f g ~> Day j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Day f g ~> Day f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Day f g ~> Day j l Source # | |
| HBifunctor Day Source # | Since: 0.3.4.0 | 
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Day f g ~> Day j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Day f g ~> Day f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Day f g ~> Day j l Source # | |
| HBifunctor These1 Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> These1 f g ~> These1 j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> These1 f g ~> These1 f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> These1 f g ~> These1 j l Source # | |
| HBifunctor (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type). (f ~> j) -> Comp f g ~> Comp j g Source # hright :: forall (g :: k -> Type) (l :: k -> Type) (f :: k -> Type). (g ~> l) -> Comp f g ~> Comp f l Source # hbimap :: forall (f :: k -> Type) (j :: k -> Type) (g :: k -> Type) (l :: k -> Type). (f ~> j) -> (g ~> l) -> Comp f g ~> Comp j l Source # | |
| HBifunctor (Product :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> Product f g ~> Product j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> Product f g ~> Product f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> Product f g ~> Product j l Source # | |
| HBifunctor (Sum :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> Sum f g ~> Sum j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> Sum f g ~> Sum f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> Sum f g ~> Sum j l Source # | |
| HBifunctor ((:*:) :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> (f :*: g) ~> (j :*: g) Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> (f :*: g) ~> (f :*: l) Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> (f :*: g) ~> (j :*: l) Source # | |
| HBifunctor ((:+:) :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> (f :+: g) ~> (j :+: g) Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> (f :+: g) ~> (f :+: l) Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> (f :+: g) ~> (j :+: l) Source # | |
| HBifunctor (Joker :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> Joker f g ~> Joker j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> Joker f g ~> Joker f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> Joker f g ~> Joker j l Source # | |
| HBifunctor (LeftF :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HBifunctor Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> LeftF f g ~> LeftF j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> LeftF f g ~> LeftF f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> LeftF f g ~> LeftF j l Source # | |
| HBifunctor (RightF :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HBifunctor Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> RightF f g ~> RightF j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> RightF f g ~> RightF f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> RightF f g ~> RightF j l Source # | |
| HBifunctor (Void3 :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> Void3 f g ~> Void3 j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> Void3 f g ~> Void3 f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> Void3 f g ~> Void3 j l Source # | |
| HBifunctor t => HBifunctor (WrapHBF t :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HBifunctor.Associative Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> WrapHBF t f g ~> WrapHBF t j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> WrapHBF t f g ~> WrapHBF t f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> WrapHBF t f g ~> WrapHBF t j l Source # | |
newtype WrappedHBifunctor t (f :: k -> Type) (g :: k -> Type) (a :: k) Source #
Useful newtype to allow us to derive an HFunctor instance from any
 instance of HBifunctor, using -XDerivingVia.
For example, because we have instance , we can
 write:HBifunctor Day
deriving via (WrappedHBifunctorDayf) instanceHFunctor(Dayf)
to give us an automatic HFunctor instance and save us some work.
Constructors
| WrapHBifunctor | |
| Fields 
 | |
Instances
| HBifunctor t => HFunctor (WrappedHBifunctor t f :: (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HFunctor.Internal Methods hmap :: forall (f0 :: k0 -> Type) (g :: k0 -> Type). (f0 ~> g) -> WrappedHBifunctor t f f0 ~> WrappedHBifunctor t f g Source # | |
| Functor (t f g) => Functor (WrappedHBifunctor t f g) Source # | |
| 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
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.
Instances
| HTraversable (LeftF f :: (k -> Type) -> k1 -> Type) Source # | |
| Defined in Data.HBifunctor | |
| HFunctor (LeftF f :: (k -> Type) -> k1 -> Type) Source # | |
| HBifunctor (LeftF :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HBifunctor Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> LeftF f g ~> LeftF j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> LeftF f g ~> LeftF f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> LeftF f g ~> LeftF j l Source # | |
| Associative (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Defined in Data.HBifunctor.Associative Associated Types type NonEmptyBy LeftF :: (Type -> Type) -> Type -> Type Source # type FunctorBy LeftF :: (Type -> Type) -> Constraint Source # Methods associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy LeftF f, FunctorBy LeftF g, FunctorBy LeftF h) => LeftF f (LeftF g h) <~> LeftF (LeftF f g) h Source # appendNE :: forall (f :: Type -> Type). LeftF (NonEmptyBy LeftF f) (NonEmptyBy LeftF f) ~> NonEmptyBy LeftF f Source # matchNE :: forall (f :: Type -> Type). FunctorBy LeftF f => NonEmptyBy LeftF f ~> (f :+: LeftF f (NonEmptyBy LeftF f)) Source # consNE :: forall (f :: Type -> Type). LeftF f (NonEmptyBy LeftF f) ~> NonEmptyBy LeftF f Source # toNonEmptyBy :: forall (f :: Type -> Type). LeftF f f ~> NonEmptyBy LeftF f Source # | |
| SemigroupIn (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | |
| Foldable f => Bifoldable (LeftF f :: Type -> Type -> Type) Source # | |
| Functor f => Bifunctor (LeftF f :: Type -> Type -> Type) Source # | |
| Traversable f => Bitraversable (LeftF f :: Type -> Type -> Type) Source # | |
| Defined in Data.HBifunctor Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> LeftF f a b -> f0 (LeftF f c d) # | |
| Applicative f => Biapplicative (LeftF f :: Type -> Type -> Type) Source # | |
| Foldable f => Foldable (LeftF f g) Source # | |
| Defined in Data.HBifunctor Methods fold :: Monoid m => LeftF f g m -> m # foldMap :: Monoid m => (a -> m) -> LeftF f g a -> 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] # 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 # | |
| Eq1 f => Eq1 (LeftF f g) Source # | |
| Ord1 f => Ord1 (LeftF f g) Source # | |
| Defined in Data.HBifunctor | |
| Read1 f => Read1 (LeftF f g) Source # | |
| Defined in Data.HBifunctor | |
| Show1 f => Show1 (LeftF f g) Source # | |
| Traversable f => Traversable (LeftF f g) Source # | |
| Defined in Data.HBifunctor | |
| Functor f => Functor (LeftF f g) Source # | |
| (Typeable g, Typeable a, Typeable f, Typeable k1, Typeable k2, Data (f a)) => Data (LeftF f g a) Source # | |
| 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 :: forall r r'. (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) # | |
| Generic (LeftF f g a) Source # | |
| Read (f a) => Read (LeftF f g a) Source # | |
| Show (f a) => Show (LeftF f g a) Source # | |
| Eq (f a) => Eq (LeftF f g a) Source # | |
| Ord (f a) => Ord (LeftF f g a) Source # | |
| Defined in Data.HBifunctor | |
| type FunctorBy (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Defined in Data.HBifunctor.Associative | |
| type NonEmptyBy (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| type Rep (LeftF f g a) Source # | |
| Defined in Data.HBifunctor | |
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.
Instances
| HTraversable (RightF g :: (k1 -> Type) -> k1 -> Type) Source # | |
| Defined in Data.HBifunctor | |
| HFunctor (RightF g :: (k1 -> Type) -> k1 -> Type) Source # | |
| HBifunctor (RightF :: (k -> Type) -> (k -> Type) -> k -> Type) Source # | |
| Defined in Data.HBifunctor Methods hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> RightF f g ~> RightF j g Source # hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> RightF f g ~> RightF f l Source # hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> RightF f g ~> RightF j l Source # | |
| HBind (RightF g :: (k2 -> Type) -> k2 -> Type) Source # | |
| Inject (RightF g :: (k2 -> Type) -> k2 -> Type) Source # | |
| Interpret (RightF g :: (k2 -> Type) -> k2 -> Type) (f :: k2 -> Type) Source # | |
| Associative (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Defined in Data.HBifunctor.Associative Associated Types type NonEmptyBy RightF :: (Type -> Type) -> Type -> Type Source # type FunctorBy RightF :: (Type -> Type) -> Constraint Source # Methods associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy RightF f, FunctorBy RightF g, FunctorBy RightF h) => RightF f (RightF g h) <~> RightF (RightF f g) h Source # appendNE :: forall (f :: Type -> Type). RightF (NonEmptyBy RightF f) (NonEmptyBy RightF f) ~> NonEmptyBy RightF f Source # matchNE :: forall (f :: Type -> Type). FunctorBy RightF f => NonEmptyBy RightF f ~> (f :+: RightF f (NonEmptyBy RightF f)) Source # consNE :: forall (f :: Type -> Type). RightF f (NonEmptyBy RightF f) ~> NonEmptyBy RightF f Source # toNonEmptyBy :: forall (f :: Type -> Type). RightF f f ~> NonEmptyBy RightF f Source # | |
| SemigroupIn (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # | |
| Foldable g => Foldable (RightF f g) Source # | |
| Defined in Data.HBifunctor Methods fold :: Monoid m => RightF f g m -> m # foldMap :: Monoid m => (a -> m) -> RightF f g a -> 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 # | |
| Eq1 g => Eq1 (RightF f g) Source # | |
| Ord1 g => Ord1 (RightF f g) Source # | |
| Defined in Data.HBifunctor | |
| Read1 g => Read1 (RightF f g) Source # | |
| 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 # | |
| Traversable g => Traversable (RightF f g) Source # | |
| Defined in Data.HBifunctor | |
| Functor g => Functor (RightF f g) Source # | |
| (Typeable f, Typeable a, Typeable g, Typeable k1, Typeable k2, Data (g a)) => Data (RightF f g a) Source # | |
| 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 :: forall r r'. (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) # | |
| Generic (RightF f g a) Source # | |
| Read (g a) => Read (RightF f g a) Source # | |
| Show (g a) => Show (RightF f g a) Source # | |
| Eq (g a) => Eq (RightF f g a) Source # | |
| Ord (g a) => Ord (RightF f g a) Source # | |
| Defined in Data.HBifunctor | |
| type FunctorBy (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Defined in Data.HBifunctor.Associative | |
| type NonEmptyBy (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| type Rep (RightF f g a) Source # | |
| Defined in Data.HBifunctor | |