multiwalk-0.3.0.1: Traverse data types via generics, acting on multiple types simultaneously.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.MultiWalk.Contains

Description

This module contains the instances and definitions supporting Multiwalk module, along with the combinators for writing MultiSub instances.

Synopsis

Documentation

type family AllMods (p :: Type -> Constraint) (as :: Spec) :: Constraint where ... Source #

Equations

AllMods p ('SpecList ls) = AllMods' p ls 
AllMods p ('SpecSelf t) = p t 
AllMods p 'SpecLeaf = () 

type family All (p :: k -> Constraint) (as :: [k]) :: Constraint where ... Source #

Equations

All p '[] = () 
All p (a ': as) = (p a, All p as) 

data GSubTag Source #

Instances

Instances details
(Generic t, HasSub' ctag (l ': ls) ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) (Rep t)) => HasSub ctag GSubTag ('SpecList (l ': ls)) t Source # 
Instance details

Defined in Control.MultiWalk.HasSub

Methods

modSub :: forall c m. (Applicative m, AllMods c ('SpecList (l ': ls))) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m (Carrier ctag s)) -> t -> m t Source #

getSub :: forall c m. (Monoid m, AllMods c ('SpecList (l ': ls))) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m) -> t -> m Source #

data SubSpec Source #

Constructors

SubSpec 

Fields

  • SelSpec

    Constructor and field selectors

  • Type

    Modifiers (used for customizing constraints)

  • Type

    Carrier type, should be equal to Carrier of type above (to be aligned with the target's generic subtypes)

Instances

Instances details
(Generic t, HasSub' ctag (l ': ls) ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) (Rep t)) => HasSub ctag GSubTag ('SpecList (l ': ls)) t Source # 
Instance details

Defined in Control.MultiWalk.HasSub

Methods

modSub :: forall c m. (Applicative m, AllMods c ('SpecList (l ': ls))) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m (Carrier ctag s)) -> t -> m t Source #

getSub :: forall c m. (Monoid m, AllMods c ('SpecList (l ': ls))) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m) -> t -> m Source #

data Spec Source #

Constructors

SpecList [SubSpec] 
SpecLeaf 
SpecSelf Type

Modifiers (used for customizing constraints)

data Under (b :: Type) (s :: SelSpec) (a :: Type) Source #

Use this for matching a subcomponent nested inside another type. Useful if you don't want to add the middle type to the list of walkable types.

Instances

Instances details
(TContains fs a, HasSub GSubTag ('SpecList '['SubSpec s a (Carrier a)]) b) => TContains fs (Under b s a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (Under b s a) -> m (ContainsCarrier (Under b s a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (Under b s a) -> m Source #

data MatchWith (s :: Type) (a :: Type) Source #

Use this for matching with another type that is coercible to the type you want.

Instances

Instances details
(TContains fs a, Coercible (Carrier a) s) => TContains fs (MatchWith s a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (MatchWith s a) -> m (ContainsCarrier (MatchWith s a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (MatchWith s a) -> m Source #

data Trav (k :: Type -> Type) (a :: Type) Source #

Use this for matching with a type inside a traversable functor.

Instances

Instances details
(Traversable f, TContains fs a) => TContains fs (Trav f a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (Trav f a) -> m (ContainsCarrier (Trav f a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (Trav f a) -> m Source #

class TContains (fs :: [Type]) (t :: Type) where Source #

Auxiliary class that keeps track of how retrieve queries and walks from their lists and apply them according to the combinators.

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier t -> m (ContainsCarrier t) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier t -> m Source #

Instances

Instances details
(FContains fs (Carrier a), QContains fs (Carrier a)) => TContains fs a Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier a -> m (ContainsCarrier a) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier a -> m Source #

(TContains fs a, Coercible (Carrier a) s) => TContains fs (MatchWith s a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (MatchWith s a) -> m (ContainsCarrier (MatchWith s a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (MatchWith s a) -> m Source #

(Traversable f, TContains fs a) => TContains fs (Trav f a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (Trav f a) -> m (ContainsCarrier (Trav f a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (Trav f a) -> m Source #

(TContains fs a, HasSub GSubTag ('SpecList '['SubSpec s a (Carrier a)]) b) => TContains fs (Under b s a) Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

tGetW :: Applicative m => FList m fs -> ContainsCarrier (Under b s a) -> m (ContainsCarrier (Under b s a)) Source #

tGetQ :: Monoid m => QList m fs -> ContainsCarrier (Under b s a) -> m Source #

class FContains (l :: [Type]) (t :: Type) where Source #

Methods

fGet :: FList m l -> t -> m t Source #

fSet :: FList m l -> (t -> m t) -> FList m l Source #

Instances

Instances details
FContains (t ': xs) t Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

fGet :: FList m (t ': xs) -> t -> m t Source #

fSet :: FList m (t ': xs) -> (t -> m t) -> FList m (t ': xs) Source #

FContains xs t => FContains (x ': xs) t Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

fGet :: FList m (x ': xs) -> t -> m t Source #

fSet :: FList m (x ': xs) -> (t -> m t) -> FList m (x ': xs) Source #

data FList :: (Type -> Type) -> [Type] -> Type where Source #

Heterogeneous list of monadic-valued functions

Constructors

FNil :: FList m '[] 
(:.:) :: (x -> m x) -> FList m xs -> FList m (x ': xs) infixr 8 

class QContains (l :: [Type]) (t :: Type) where Source #

Methods

qGet :: QList m l -> t -> m Source #

qSet :: QList m l -> (t -> m) -> QList m l Source #

Instances

Instances details
QContains (t ': xs) t Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

qGet :: QList m (t ': xs) -> t -> m Source #

qSet :: QList m (t ': xs) -> (t -> m) -> QList m (t ': xs) Source #

QContains xs t => QContains (x ': xs) t Source # 
Instance details

Defined in Control.MultiWalk.Contains

Methods

qGet :: QList m (x ': xs) -> t -> m Source #

qSet :: QList m (x ': xs) -> (t -> m) -> QList m (x ': xs) Source #

data QList :: Type -> [Type] -> Type where Source #

Heterogeneous list of queries

Constructors

QNil :: QList m '[] 
(:?:) :: (x -> m) -> QList m xs -> QList m (x ': xs) infixr 8 

type HasSub tag ls t = HasSub MWCTag tag ls t Source #

type family ContainsCarrier (a :: Type) :: Type where ... Source #

Equations

ContainsCarrier (Under b s a) = b 
ContainsCarrier (MatchWith s a) = s 
ContainsCarrier (Trav f a) = f (Carrier a) 
ContainsCarrier a = a 

data MWCTag Source #

Instances

Instances details
type Carrier MWCTag a Source # 
Instance details

Defined in Control.MultiWalk.Contains

type Carrier MWCTag a Source # 
Instance details

Defined in Control.MultiWalk.Contains

modSubWithFList :: forall tag ls t fs m. (HasSub tag ls t, Applicative m, AllMods (TContains fs) ls) => FList m fs -> t -> m t Source #

Modify (only) substructures by applying functions from FList.

getSubWithQList :: forall tag ls t fs m. (HasSub tag ls t, Monoid m, AllMods (TContains fs) ls) => QList m fs -> t -> m Source #

Query (only) substructures by applying functions from QList.