Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Transformation t, Functor (g (Domain t))) => Functor t g where
- class (Transformation t, Foldable (g (Domain t))) => Foldable t g where
- class (Transformation t, Traversable (g (Domain t))) => Traversable t g where
- data Product g1 g2 (p :: * -> *) (q :: * -> *) = Pair {}
- fmap :: Functor t g => t -> g (Domain t) (Domain t) -> g (Codomain t) (Codomain t)
Documentation
class (Transformation t, Functor (g (Domain t))) => Functor t g where Source #
Like Functor
except it maps all descendants and not only immediate children
class (Transformation t, Foldable (g (Domain t))) => Foldable t g where Source #
Like Foldable
except it folds all descendants and not only immediate children
class (Transformation t, Traversable (g (Domain t))) => Traversable t g where Source #
Like Traversable
except it folds all descendants and not only immediate children
Instances
(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Product g h) Source # | |
data Product g1 g2 (p :: * -> *) (q :: * -> *) Source #
Like Product
for data types with two type constructor parameters
Instances
(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Product g h) Source # | |
(Functor t g, Functor t h) => Functor t (Product g h) Source # | |
Applicative (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep | |
Apply (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep (<*>) :: forall (p0 :: k -> Type) (q :: k -> Type). Product g h p (p0 ~> q) -> Product g h p p0 -> Product g h p q liftA2 :: (forall (a :: k). p0 a -> q a -> r a) -> Product g h p p0 -> Product g h p q -> Product g h p r liftA3 :: (forall (a :: k). p0 a -> q a -> r a -> s a) -> Product g h p p0 -> Product g h p q -> Product g h p r -> Product g h p s | |
Distributive (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep collect :: forall f1 a (f2 :: k -> Type). Functor f1 => (a -> Product g h p f2) -> f1 a -> Product g h p (Compose f1 f2) distribute :: forall f1 (f2 :: k -> Type). Functor f1 => f1 (Product g h p f2) -> Product g h p (Compose f1 f2) cotraverse :: Functor m => (forall (a :: k). m (p0 a) -> q a) -> m (Product g h p p0) -> Product g h p q | |
DistributiveTraversable (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Product g h p f2) -> f1 a -> Product g h p (Compose f1 f2) distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Product g h p f2) -> Product g h p (Compose f1 f2) cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Product g h p f2) -> Product g h p f | |
Foldable (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep | |
Functor (Product g1 g2 p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep | |
Traversable (Product g h p :: (Type -> Type) -> Type) Source # | |
Defined in Transformation.Deep traverse :: Applicative m => (forall (a :: k). p0 a -> m (q a)) -> Product g h p p0 -> m (Product g h p q) sequence :: forall m (p0 :: k -> Type). Applicative m => Product g h p (Compose m p0) -> m (Product g h p p0) | |
(Typeable p, Typeable q, Typeable g1, Typeable g2, Data (q (g1 p p)), Data (q (g2 p p))) => Data (Product g1 g2 p q) Source # | |
Defined in Transformation.Deep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product g1 g2 p q -> c (Product g1 g2 p q) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product g1 g2 p q) # toConstr :: Product g1 g2 p q -> Constr # dataTypeOf :: Product g1 g2 p q -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product g1 g2 p q)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product g1 g2 p q)) # gmapT :: (forall b. Data b => b -> b) -> Product g1 g2 p q -> Product g1 g2 p q # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product g1 g2 p q -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product g1 g2 p q -> r # gmapQ :: (forall d. Data d => d -> u) -> Product g1 g2 p q -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product g1 g2 p q -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product g1 g2 p q -> m (Product g1 g2 p q) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product g1 g2 p q -> m (Product g1 g2 p q) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product g1 g2 p q -> m (Product g1 g2 p q) # | |
(Show (q (g1 p p)), Show (q (g2 p p))) => Show (Product g1 g2 p q) Source # | |