Safe Haskell | None |
---|---|
Language | Haskell2010 |
Import this module qualified, like this:
import qualified Rank2
This will bring into scope the standard classes Functor
, Applicative
, Foldable
, and Traversable
, but with a
Rank2.
prefix and a twist that their methods operate on a heterogenous collection. The same property is shared by
the two less standard classes Apply
and Distributive
.
Synopsis
- class Functor g where
- (<$>) :: (forall a. p a -> q a) -> g p -> g q
- class Functor g => Apply g where
- class Apply g => Applicative g where
- pure :: (forall a. f a) -> g f
- class Foldable g where
- class (Functor g, Foldable g) => Traversable g where
- traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q)
- sequence :: Applicative m => g (Compose m p) -> m (g p)
- class DistributiveTraversable g => Distributive g where
- collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2)
- distribute :: Functor f1 => f1 (g f2) -> g (Compose f1 f2)
- cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (g p) -> g q
- class Functor g => DistributiveTraversable (g :: (k -> *) -> *) where
- collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2)
- distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose f1 f2)
- cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f
- distributeJoin :: (Distributive g, Monad f) => f (g f) -> g f
- newtype Compose g p q = Compose {
- getCompose :: g (Compose p q)
- data Empty f = Empty
- newtype Only a f = Only {
- fromOnly :: f a
- newtype Flip g a f = Flip {
- unFlip :: g (f a)
- newtype Identity g f = Identity {
- runIdentity :: g f
- data Product (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type = Pair (f a) (g a)
- data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type
- newtype Arrow p q a = Arrow {
- apply :: p a -> q a
- type (~>) = Arrow
- ($) :: Arrow p q a -> p a -> q a
- fst :: Product g h p -> g p
- snd :: Product g h p -> h p
- ap :: Apply g => g (p ~> q) -> g p -> g q
- fmap :: Functor g => (forall a. p a -> q a) -> g p -> g q
- liftA4 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a) -> g p -> g q -> g r -> g s -> g t
- liftA5 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a -> u a) -> g p -> g q -> g r -> g s -> g t -> g u
- fmapTraverse :: (DistributiveTraversable g, Traversable f) => (forall a. f (t a) -> u a) -> f (g t) -> g u
- liftA2Traverse1 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. f (t a) -> u a -> v a) -> f (g t) -> g u -> g v
- liftA2Traverse2 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. t a -> f (u a) -> v a) -> g t -> f (g u) -> g v
- liftA2TraverseBoth :: (Apply g, DistributiveTraversable g, Traversable f1, Traversable f2) => (forall a. f1 (t a) -> f2 (u a) -> v a) -> f1 (g t) -> f2 (g u) -> g v
- distributeWith :: (Distributive g, Functor f) => (forall i. f (a i) -> b i) -> f (g a) -> g b
- distributeWithTraversable :: (DistributiveTraversable g, Traversable m) => (forall a. m (p a) -> q a) -> m (g p) -> g q
Rank 2 classes
class Functor g where Source #
Equivalent of Functor
for rank 2 data types, satisfying the usual functor laws
id <$> g == g (p . q) <$> g == p <$> (q <$> g)
Instances
Functor (U1 :: (k -> Type) -> Type) Source # | |
Functor (V1 :: (k -> Type) -> Type) Source # | |
Functor (Proxy :: (k -> Type) -> Type) Source # | |
Functor (Empty :: (k -> Type) -> Type) Source # | |
Functor f => Functor (Rec1 f :: (k -> Type) -> Type) Source # | |
Functor (Const a :: (k -> Type) -> Type) Source # | |
Functor (Only a :: (k -> Type) -> Type) Source # | |
Functor g => Functor (Identity g :: (k -> Type) -> Type) Source # | |
(Functor f, Functor g) => Functor (f :*: g :: (k -> Type) -> Type) Source # | |
(Functor f, Functor g) => Functor (f :+: g :: (k -> Type) -> Type) Source # | |
Functor (K1 i c :: (k -> Type) -> Type) Source # | |
(Functor g, Functor h) => Functor (Sum g h :: (k -> Type) -> Type) Source # | |
(Functor g, Functor h) => Functor (Product g h :: (k -> Type) -> Type) Source # | |
Functor f => Functor (M1 i c f :: (k -> Type) -> Type) Source # | |
(Functor g, Functor p) => Functor (Compose g p :: (k -> Type) -> Type) Source # | |
Functor g => Functor (Flip g a :: (k -> Type) -> Type) Source # | |
class Functor g => Apply g where Source #
Subclass of Functor
halfway to Applicative
, satisfying
(.) <$> u <*> v <*> w == u <*> (v <*> w)
(<*>) :: g (p ~> q) -> g p -> g q infixl 4 Source #
Equivalent of <*>
for rank 2 data types
liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #
Equivalent of liftA2
for rank 2 data types
liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #
Equivalent of liftA3
for rank 2 data types
Instances
Apply (U1 :: (k -> Type) -> Type) Source # | |
Apply (V1 :: (k -> Type) -> Type) Source # | |
Apply (Proxy :: (k -> Type) -> Type) Source # | |
Apply (Empty :: (k -> Type) -> Type) Source # | |
Apply f => Apply (Rec1 f :: (k -> Type) -> Type) Source # | |
Semigroup x => Apply (Const x :: (k -> Type) -> Type) Source # | |
Apply (Only x :: (k -> Type) -> Type) Source # | |
Apply g => Apply (Identity g :: (k -> Type) -> Type) Source # | |
Defined in Rank2 (<*>) :: Identity g (p ~> q) -> Identity g p -> Identity g q Source # liftA2 :: (forall (a :: k0). p a -> q a -> r a) -> Identity g p -> Identity g q -> Identity g r Source # liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Identity g p -> Identity g q -> Identity g r -> Identity g s Source # | |
(Apply f, Apply g) => Apply (f :*: g :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
Semigroup c => Apply (K1 i c :: (k -> Type) -> Type) Source # | |
(Apply g, Apply h) => Apply (Product g h :: (k -> Type) -> Type) Source # | |
Defined in Rank2 (<*>) :: Product g h (p ~> q) -> Product g h p -> Product g h q Source # liftA2 :: (forall (a :: k0). p a -> q a -> r a) -> Product g h p -> Product g h q -> Product g h r Source # liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Product g h p -> Product g h q -> Product g h r -> Product g h s Source # | |
Apply f => Apply (M1 i c f :: (k -> Type) -> Type) Source # | |
(Apply g, Applicative p) => Apply (Compose g p :: (k -> Type) -> Type) Source # | |
Defined in Rank2 (<*>) :: Compose g p (p0 ~> q) -> Compose g p p0 -> Compose g p q Source # liftA2 :: (forall (a :: k0). p0 a -> q a -> r a) -> Compose g p p0 -> Compose g p q -> Compose g p r Source # liftA3 :: (forall (a :: k0). p0 a -> q a -> r a -> s a) -> Compose g p p0 -> Compose g p q -> Compose g p r -> Compose g p s Source # | |
Applicative g => Apply (Flip g a :: (k -> Type) -> Type) Source # | |
Defined in Rank2 |
class Apply g => Applicative g where Source #
Equivalent of Applicative
for rank 2 data types
Instances
Applicative (Proxy :: (k -> Type) -> Type) Source # | |
Applicative (Empty :: (k -> Type) -> Type) Source # | |
Applicative f => Applicative (Rec1 f :: (k -> Type) -> Type) Source # | |
(Semigroup x, Monoid x) => Applicative (Const x :: (k -> Type) -> Type) Source # | |
Applicative (Only x :: (k -> Type) -> Type) Source # | |
Applicative g => Applicative (Identity g :: (k -> Type) -> Type) Source # | |
(Applicative f, Applicative g) => Applicative (f :*: g :: (k -> Type) -> Type) Source # | |
(Semigroup c, Monoid c) => Applicative (K1 i c :: (k -> Type) -> Type) Source # | |
(Applicative g, Applicative h) => Applicative (Product g h :: (k -> Type) -> Type) Source # | |
Applicative f => Applicative (M1 i c f :: (k -> Type) -> Type) Source # | |
(Applicative g, Applicative p) => Applicative (Compose g p :: (k -> Type) -> Type) Source # | |
Applicative g => Applicative (Flip g a :: (k -> Type) -> Type) Source # | |
class Foldable g where Source #
Equivalent of Foldable
for rank 2 data types
Instances
class (Functor g, Foldable g) => Traversable g where Source #
Equivalent of Traversable
for rank 2 data types
traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #
sequence :: Applicative m => g (Compose m p) -> m (g p) Source #
Instances
class DistributiveTraversable g => Distributive g where Source #
Equivalent of Distributive
for rank 2 data types
collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2) Source #
distribute :: Functor f1 => f1 (g f2) -> g (Compose f1 f2) Source #
cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
Dual of traverse
, equivalent of cotraverse
for rank 2 data types
Instances
Distributive (Proxy :: (k -> Type) -> Type) Source # | |
Distributive (Empty :: (k -> Type) -> Type) Source # | |
Distributive f => Distributive (Rec1 f :: (k -> Type) -> Type) Source # | |
Distributive (Only x :: (k -> Type) -> Type) Source # | |
Distributive g => Distributive (Identity g :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
(Distributive f, Distributive g) => Distributive (f :*: g :: (k -> Type) -> Type) Source # | |
(Distributive g, Distributive h) => Distributive (Product g h :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
Distributive f => Distributive (M1 i c f :: (k -> Type) -> Type) Source # | |
(Distributive g, Distributive p) => Distributive (Compose g p :: (k -> Type) -> Type) Source # | |
Defined in Rank2 |
class Functor g => DistributiveTraversable (g :: (k -> *) -> *) where Source #
A weaker Distributive
that requires Traversable
to use, not just a Functor
.
Nothing
collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2) Source #
distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose f1 f2) Source #
cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #
cotraverseTraversable :: (Traversable m, Distributive g) => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
Instances
distributeJoin :: (Distributive g, Monad f) => f (g f) -> g f Source #
A variant of distribute
convenient with Monad
instances
Rank 2 data types
newtype Compose g p q Source #
Equivalent of Compose
for rank 2 data types
Compose | |
|
Instances
(DistributiveTraversable g, Distributive p) => DistributiveTraversable (Compose g p :: (k -> Type) -> Type) Source # | |
Defined in Rank2 collectTraversable :: Traversable f1 => (a -> Compose g p f2) -> f1 a -> Compose g p (Compose0 f1 f2) Source # distributeTraversable :: Traversable f1 => f1 (Compose g p f2) -> Compose g p (Compose0 f1 f2) Source # cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Compose g p f2) -> Compose g p f Source # | |
(Distributive g, Distributive p) => Distributive (Compose g p :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
(Applicative g, Applicative p) => Applicative (Compose g p :: (k -> Type) -> Type) Source # | |
(Apply g, Applicative p) => Apply (Compose g p :: (k -> Type) -> Type) Source # | |
Defined in Rank2 (<*>) :: Compose g p (p0 ~> q) -> Compose g p p0 -> Compose g p q Source # liftA2 :: (forall (a :: k0). p0 a -> q a -> r a) -> Compose g p p0 -> Compose g p q -> Compose g p r Source # liftA3 :: (forall (a :: k0). p0 a -> q a -> r a -> s a) -> Compose g p p0 -> Compose g p q -> Compose g p r -> Compose g p s Source # | |
(Traversable g, Traversable p) => Traversable (Compose g p :: (k -> Type) -> Type) Source # | |
(Foldable g, Foldable p) => Foldable (Compose g p :: (k -> Type) -> Type) Source # | |
(Functor g, Functor p) => Functor (Compose g p :: (k -> Type) -> Type) Source # | |
Eq (g (Compose p q)) => Eq (Compose g p q) Source # | |
Ord (g (Compose p q)) => Ord (Compose g p q) Source # | |
Defined in Rank2 compare :: Compose g p q -> Compose g p q -> Ordering # (<) :: Compose g p q -> Compose g p q -> Bool # (<=) :: Compose g p q -> Compose g p q -> Bool # (>) :: Compose g p q -> Compose g p q -> Bool # (>=) :: Compose g p q -> Compose g p q -> Bool # | |
Show (g (Compose p q)) => Show (Compose g p q) Source # | |
A rank-2 equivalent of ()
, a zero-element tuple
Instances
DistributiveTraversable (Empty :: (k -> Type) -> Type) Source # | |
Defined in Rank2 collectTraversable :: Traversable f1 => (a -> Empty f2) -> f1 a -> Empty (Compose f1 f2) Source # distributeTraversable :: Traversable f1 => f1 (Empty f2) -> Empty (Compose f1 f2) Source # cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Empty f2) -> Empty f Source # | |
Distributive (Empty :: (k -> Type) -> Type) Source # | |
Applicative (Empty :: (k -> Type) -> Type) Source # | |
Apply (Empty :: (k -> Type) -> Type) Source # | |
Traversable (Empty :: (k -> Type) -> Type) Source # | |
Foldable (Empty :: (k -> Type) -> Type) Source # | |
Functor (Empty :: (k -> Type) -> Type) Source # | |
Eq (Empty f) Source # | |
Ord (Empty f) Source # | |
Show (Empty f) Source # | |
A rank-2 tuple of only one element
Instances
DistributiveTraversable (Only x :: (k -> Type) -> Type) Source # | |
Defined in Rank2 collectTraversable :: Traversable f1 => (a -> Only x f2) -> f1 a -> Only x (Compose f1 f2) Source # distributeTraversable :: Traversable f1 => f1 (Only x f2) -> Only x (Compose f1 f2) Source # cotraverseTraversable :: Traversable f1 => (forall (x0 :: k0). f1 (f2 x0) -> f x0) -> f1 (Only x f2) -> Only x f Source # | |
Distributive (Only x :: (k -> Type) -> Type) Source # | |
Applicative (Only x :: (k -> Type) -> Type) Source # | |
Apply (Only x :: (k -> Type) -> Type) Source # | |
Traversable (Only x :: (k -> Type) -> Type) Source # | |
Foldable (Only x :: (k -> Type) -> Type) Source # | |
Functor (Only a :: (k -> Type) -> Type) Source # | |
Eq (f a) => Eq (Only a f) Source # | |
Ord (f a) => Ord (Only a f) Source # | |
Show (f a) => Show (Only a f) Source # | |
A nested parametric type represented as a rank-2 type
Instances
Applicative g => Applicative (Flip g a :: (k -> Type) -> Type) Source # | |
Applicative g => Apply (Flip g a :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
Traversable g => Traversable (Flip g a :: (k -> Type) -> Type) Source # | |
Foldable g => Foldable (Flip g a :: (k -> Type) -> Type) Source # | |
Functor g => Functor (Flip g a :: (k -> Type) -> Type) Source # | |
Eq (g (f a)) => Eq (Flip g a f) Source # | |
Ord (g (f a)) => Ord (Flip g a f) Source # | |
Show (g (f a)) => Show (Flip g a f) Source # | |
Semigroup (g (f a)) => Semigroup (Flip g a f) Source # | |
Monoid (g (f a)) => Monoid (Flip g a f) Source # | |
Equivalent of Identity
for rank 2 data types
Identity | |
|
Instances
data Product (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type #
Lifted product of functors.
Pair (f a) (g a) |
Instances
Generic1 (Product f g :: k -> Type) | |
(DistributiveTraversable g, DistributiveTraversable h) => DistributiveTraversable (Product g h :: (k -> Type) -> Type) Source # | |
Defined in Rank2 collectTraversable :: Traversable f1 => (a -> Product g h f2) -> f1 a -> Product g h (Compose f1 f2) Source # distributeTraversable :: Traversable f1 => f1 (Product g h f2) -> Product g h (Compose f1 f2) Source # cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Product g h f2) -> Product g h f Source # | |
(Distributive g, Distributive h) => Distributive (Product g h :: (k -> Type) -> Type) Source # | |
Defined in Rank2 | |
(Applicative g, Applicative h) => Applicative (Product g h :: (k -> Type) -> Type) Source # | |
(Apply g, Apply h) => Apply (Product g h :: (k -> Type) -> Type) Source # | |
Defined in Rank2 (<*>) :: Product g h (p ~> q) -> Product g h p -> Product g h q Source # liftA2 :: (forall (a :: k0). p a -> q a -> r a) -> Product g h p -> Product g h q -> Product g h r Source # liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Product g h p -> Product g h q -> Product g h r -> Product g h s Source # | |
(Traversable g, Traversable h) => Traversable (Product g h :: (k -> Type) -> Type) Source # | |
(Foldable g, Foldable h) => Foldable (Product g h :: (k -> Type) -> Type) Source # | |
(Functor g, Functor h) => Functor (Product g h :: (k -> Type) -> Type) Source # | |
(Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Product f g) | Since: base-4.9.0.0 |
(MonadFix f, MonadFix g) => MonadFix (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Foldable f, Foldable g) => Foldable (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product fold :: Monoid m => Product f g m -> m # foldMap :: Monoid m => (a -> m) -> Product f g a -> m # foldr :: (a -> b -> b) -> b -> Product f g a -> b # foldr' :: (a -> b -> b) -> b -> Product f g a -> b # foldl :: (b -> a -> b) -> b -> Product f g a -> b # foldl' :: (b -> a -> b) -> b -> Product f g a -> b # foldr1 :: (a -> a -> a) -> Product f g a -> a # foldl1 :: (a -> a -> a) -> Product f g a -> a # toList :: Product f g a -> [a] # null :: Product f g a -> Bool # length :: Product f g a -> Int # elem :: Eq a => a -> Product f g a -> Bool # maximum :: Ord a => Product f g a -> a # minimum :: Ord a => Product f g a -> a # | |
(Traversable f, Traversable g) => Traversable (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Eq1 f, Eq1 g) => Eq1 (Product f g) | Since: base-4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Read1 f, Read1 g) => Read1 (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product f g a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] # | |
(Show1 f, Show1 g) => Show1 (Product f g) | Since: base-4.9.0.0 |
(MonadZip f, MonadZip g) => MonadZip (Product f g) | Since: base-4.9.0.0 |
(Alternative f, Alternative g) => Alternative (Product f g) | Since: base-4.9.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) | Since: base-4.9.0.0 |
(Distributive f, Distributive g) => Distributive (Product f g) | |
Defined in Data.Distributive | |
(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) | Since: base-4.9.0.0 |
(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Product f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Product f g a -> c (Product f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) # toConstr :: Product f g a -> Constr # dataTypeOf :: Product f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) # gmapT :: (forall b. Data b => b -> b) -> Product f g a -> Product f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Product f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product compare :: Product f g a -> Product f g a -> Ordering # (<) :: Product f g a -> Product f g a -> Bool # (<=) :: Product f g a -> Product f g a -> Bool # (>) :: Product f g a -> Product f g a -> Bool # (>=) :: Product f g a -> Product f g a -> Bool # | |
(Read1 f, Read1 g, Read a) => Read (Product f g a) | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Product f g a) | Since: base-4.9.0.0 |
Generic (Product f g a) | |
type Rep1 (Product f g :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product type Rep1 (Product f g :: k -> Type) = D1 (MetaData "Product" "Data.Functor.Product" "base" False) (C1 (MetaCons "Pair" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 g))) | |
type Rep (Product f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product type Rep (Product f g a) = D1 (MetaData "Product" "Data.Functor.Product" "base" False) (C1 (MetaCons "Pair" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g a)))) |
data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type #
Lifted sum of functors.
Instances
Generic1 (Sum f g :: k -> Type) | |
(Traversable g, Traversable h) => Traversable (Sum g h :: (k -> Type) -> Type) Source # | |
(Foldable g, Foldable h) => Foldable (Sum g h :: (k -> Type) -> Type) Source # | |
(Functor g, Functor h) => Functor (Sum g h :: (k -> Type) -> Type) Source # | |
(Functor f, Functor g) => Functor (Sum f g) | Since: base-4.9.0.0 |
(Foldable f, Foldable g) => Foldable (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum fold :: Monoid m => Sum f g m -> m # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m # foldr :: (a -> b -> b) -> b -> Sum f g a -> b # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b # foldl :: (b -> a -> b) -> b -> Sum f g a -> b # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b # foldr1 :: (a -> a -> a) -> Sum f g a -> a # foldl1 :: (a -> a -> a) -> Sum f g a -> a # elem :: Eq a => a -> Sum f g a -> Bool # maximum :: Ord a => Sum f g a -> a # minimum :: Ord a => Sum f g a -> a # | |
(Traversable f, Traversable g) => Traversable (Sum f g) | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Sum f g) | Since: base-4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Read1 f, Read1 g) => Read1 (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Show1 f, Show1 g) => Show1 (Sum f g) | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) | Since: base-4.9.0.0 |
(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Sum f g a -> c (Sum f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum f g a) # toConstr :: Sum f g a -> Constr # dataTypeOf :: Sum f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum f g a)) # gmapT :: (forall b. Data b => b -> b) -> Sum f g a -> Sum f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Read1 f, Read1 g, Read a) => Read (Sum f g a) | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Sum f g a) | Since: base-4.9.0.0 |
Generic (Sum f g a) | |
type Rep1 (Sum f g :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum type Rep1 (Sum f g :: k -> Type) = D1 (MetaData "Sum" "Data.Functor.Sum" "base" False) (C1 (MetaCons "InL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)) :+: C1 (MetaCons "InR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 g))) | |
type Rep (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum type Rep (Sum f g a) = D1 (MetaData "Sum" "Data.Functor.Sum" "base" False) (C1 (MetaCons "InL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))) :+: C1 (MetaCons "InR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g a)))) |
Wrapper for functions that map the argument constructor type
Method synonyms and helper functions
liftA4 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a) -> g p -> g q -> g r -> g s -> g t Source #
liftA5 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a -> u a) -> g p -> g q -> g r -> g s -> g t -> g u Source #
fmapTraverse :: (DistributiveTraversable g, Traversable f) => (forall a. f (t a) -> u a) -> f (g t) -> g u Source #
Like fmap
, but traverses over its argument
liftA2Traverse1 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. f (t a) -> u a -> v a) -> f (g t) -> g u -> g v Source #
Like liftA2
, but traverses over its first argument
liftA2Traverse2 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. t a -> f (u a) -> v a) -> g t -> f (g u) -> g v Source #
Like liftA2
, but traverses over its second argument
liftA2TraverseBoth :: (Apply g, DistributiveTraversable g, Traversable f1, Traversable f2) => (forall a. f1 (t a) -> f2 (u a) -> v a) -> f1 (g t) -> f2 (g u) -> g v Source #
Like liftA2
, but traverses over both its arguments
distributeWith :: (Distributive g, Functor f) => (forall i. f (a i) -> b i) -> f (g a) -> g b Source #
Deprecated: Use cotraverse instead.
Synonym for cotraverse
distributeWithTraversable :: (DistributiveTraversable g, Traversable m) => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
Deprecated: Use cotraverseTraversable instead.
Synonym for cotraverseTraversable