Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module is the heart of multiwalk, providing generic instances for modifying and querying data types.
Documentation
class HasSub ctag tag (ls :: Spec) t where Source #
modSub :: forall c m. (Applicative m, AllMods c 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 ls) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m) -> t -> m Source #
Instances
HasSub tag (ctag :: k) 'SpecLeaf t Source # | |
Defined in Control.MultiWalk.HasSub | |
(Generic t, HasSub' ctag (l ': ls) ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) (Rep t)) => HasSub ctag GSubTag ('SpecList (l ': ls)) t Source # | |
Defined in Control.MultiWalk.HasSub 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 # | |
Carrier tag s ~ t => HasSub tag (ctag :: k) ('SpecSelf s) t Source # | |
Defined in Control.MultiWalk.HasSub modSub :: forall c m. (Applicative m, AllMods c ('SpecSelf s)) => Proxy c -> (forall s0. c s0 => Proxy s0 -> Carrier tag s0 -> m (Carrier tag s0)) -> t -> m t Source # getSub :: forall c m. (Monoid m, AllMods c ('SpecSelf s)) => Proxy c -> (forall s0. c s0 => Proxy s0 -> Carrier tag s0 -> m) -> t -> m Source # |
Instances
(Generic t, HasSub' ctag (l ': ls) ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) (Rep t)) => HasSub ctag GSubTag ('SpecList (l ': ls)) t Source # | |
Defined in Control.MultiWalk.HasSub 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 # |
type family Carrier ctag a :: Type Source #
Instances
type Carrier MWCTag a Source # | |
Defined in Control.MultiWalk.Contains | |
type Carrier MWCTag a Source # | |
Defined in Control.MultiWalk.Contains |
type family All (p :: k -> Constraint) (as :: [k]) :: Constraint where ... Source #
type family AllMods (p :: Type -> Constraint) (as :: Spec) :: Constraint where ... Source #
Instances
(Generic t, HasSub' ctag (l ': ls) ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) (Rep t)) => HasSub ctag GSubTag ('SpecList (l ': ls)) t Source # | |
Defined in Control.MultiWalk.HasSub 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 # |