deep-transformations-0.2.1.1: Deep natural and unnatural tree transformations, including attribute grammars
Safe HaskellSafe-Inferred
LanguageHaskell2010

Transformation.Deep

Description

Type classes Functor, Foldable, and Traversable that correspond to the standard type classes of the same name, but applying the given transformation to every descendant of the given tree node. The corresponding classes in the Transformation.Shallow module operate only on the immediate children, while those from the Transformation.Full module include the argument node itself.

Synopsis

Documentation

class (Transformation t, Functor (g (Domain t))) => Functor t g where Source #

Like Transformation.Shallow.Functor except it maps all descendants and not only immediate children

Methods

(<$>) :: t -> g (Domain t) (Domain t) -> g (Codomain t) (Codomain t) infixl 4 Source #

Instances

Instances details
(Functor t g, Functor t h) => Functor t (Product g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: t -> Product g h (Domain t) (Domain t) -> Product g h (Codomain t) (Codomain t) Source #

(Functor t g, Functor t h) => Functor t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: t -> Sum g h (Domain t) (Domain t) -> Sum g h (Codomain t) (Codomain t) Source #

class (Transformation t, Foldable (g (Domain t))) => Foldable t g where Source #

Like Transformation.Shallow.Foldable except it folds all descendants and not only immediate children

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> g (Domain t) (Domain t) -> m Source #

Instances

Instances details
(Foldable t g, Foldable t h, Codomain t ~ (Const m :: Type -> Type)) => Foldable t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Sum g h (Domain t) (Domain t) -> m Source #

class (Transformation t, Traversable (g (Domain t))) => Traversable t g where Source #

Like Transformation.Shallow.Traversable except it folds all descendants and not only immediate children

Methods

traverse :: Codomain t ~ Compose m f => t -> g (Domain t) (Domain t) -> m (g f f) Source #

Instances

Instances details
(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Product g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Product g h (Domain t) (Domain t) -> m (Product g h f f) Source #

(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Sum g h (Domain t) (Domain t) -> m (Sum g h f f) Source #

data Product g h (d :: Type -> Type) (s :: Type -> Type) Source #

Like Product for data types with two type constructor parameters

Constructors

Pair 

Fields

  • fst :: s (g d d)
     
  • snd :: s (h d d)
     

Instances

Instances details
(Functor t g, Functor t h) => Functor t (Product g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: t -> Product g h (Domain t) (Domain t) -> Product g h (Codomain t) (Codomain t) Source #

(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Product g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Product g h (Domain t) (Domain t) -> m (Product g h f f) Source #

Applicative (Product g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

pure :: (forall (a :: k). f a) -> Product g h p f #

Apply (Product g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<*>) :: 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 # 
Instance details

Defined in Transformation.Deep

Methods

collect :: forall p0 a (q :: k1 -> Type). Functor p0 => (a -> Product g h p q) -> p0 a -> Product g h p (Compose p0 q) #

distribute :: forall p0 (q :: k1 -> Type). Functor p0 => p0 (Product g h p q) -> Product g h p (Compose p0 q) #

cotraverse :: Functor m => (forall (a :: k1). 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 # 
Instance details

Defined in Transformation.Deep

Methods

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 # 
Instance details

Defined in Transformation.Deep

Methods

foldMap :: Monoid m => (forall (a :: k). p0 a -> m) -> Product g h p p0 -> m #

Functor (Product g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: (forall (a :: k). p0 a -> q a) -> Product g h p p0 -> Product g h p q #

Traversable (Product g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

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 # 
Instance details

Defined in Transformation.Deep

Methods

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 # 
Instance details

Defined in Transformation.Deep

Methods

showsPrec :: Int -> Product g1 g2 p q -> ShowS #

show :: Product g1 g2 p q -> String #

showList :: [Product g1 g2 p q] -> ShowS #

data Sum g h (d :: Type -> Type) (s :: Type -> Type) Source #

Like Sum for data types with two type constructor parameters

Constructors

InL (s (g d d)) 
InR (s (h d d)) 

Instances

Instances details
(Foldable t g, Foldable t h, Codomain t ~ (Const m :: Type -> Type)) => Foldable t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Sum g h (Domain t) (Domain t) -> m Source #

(Functor t g, Functor t h) => Functor t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: t -> Sum g h (Domain t) (Domain t) -> Sum g h (Codomain t) (Codomain t) Source #

(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Sum g h) Source # 
Instance details

Defined in Transformation.Deep

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Sum g h (Domain t) (Domain t) -> m (Sum g h f f) Source #

Foldable (Sum g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

foldMap :: Monoid m => (forall (a :: k). p0 a -> m) -> Sum g h p p0 -> m #

Functor (Sum g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

(<$>) :: (forall (a :: k). p0 a -> q a) -> Sum g h p p0 -> Sum g h p q #

Traversable (Sum g h p :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Transformation.Deep

Methods

traverse :: Applicative m => (forall (a :: k). p0 a -> m (q a)) -> Sum g h p p0 -> m (Sum g h p q) #

sequence :: forall m (p0 :: k -> Type). Applicative m => Sum g h p (Compose m p0) -> m (Sum g h p p0) #

(Typeable p, Typeable q, Typeable g1, Typeable g2, Data (q (g1 p p)), Data (q (g2 p p))) => Data (Sum g1 g2 p q) Source # 
Instance details

Defined in Transformation.Deep

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum g1 g2 p q -> c (Sum g1 g2 p q) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum g1 g2 p q) #

toConstr :: Sum g1 g2 p q -> Constr #

dataTypeOf :: Sum g1 g2 p q -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum g1 g2 p q)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum g1 g2 p q)) #

gmapT :: (forall b. Data b => b -> b) -> Sum g1 g2 p q -> Sum g1 g2 p q #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum g1 g2 p q -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum g1 g2 p q -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sum g1 g2 p q -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum g1 g2 p q -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum g1 g2 p q -> m (Sum g1 g2 p q) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum g1 g2 p q -> m (Sum g1 g2 p q) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum g1 g2 p q -> m (Sum g1 g2 p q) #

(Show (q (g1 p p)), Show (q (g2 p p))) => Show (Sum g1 g2 p q) Source # 
Instance details

Defined in Transformation.Deep

Methods

showsPrec :: Int -> Sum g1 g2 p q -> ShowS #

show :: Sum g1 g2 p q -> String #

showList :: [Sum g1 g2 p q] -> ShowS #

fmap :: Functor t g => t -> g (Domain t) (Domain t) -> g (Codomain t) (Codomain t) Source #

Alphabetical synonym for <$>

eitherFromSum :: Sum g h d s -> Either (s (g d d)) (s (h d d)) Source #

Equivalent of either