-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Traverse data types via generics, acting on multiple types simultaneously. -- -- This library provides functionality for traversing data types -- recursively, acting on multiple types during the same traversal. In -- spirit, it is similar to the Walk type class from Pandoc.Walk, but -- generalizes it by allowing multiple types to be targeted by the -- traversal. In general, it only requires an Applicative constraint on -- the action, making it suitable for situations where you don't have a -- Monad. @package multiwalk @version 0.3.0.1 -- | This module is the heart of multiwalk, providing generic instances for -- modifying and querying data types. module Control.MultiWalk.HasSub class HasSub ctag tag (ls :: Spec) t modSub :: forall c m. (HasSub ctag tag ls t, Applicative m, AllMods c ls) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m (Carrier ctag s)) -> t -> m t getSub :: forall c m. (HasSub ctag tag ls t, Monoid m, AllMods c ls) => Proxy c -> (forall s. c s => Proxy s -> Carrier ctag s -> m) -> t -> m data Spec SpecList :: [SubSpec] -> Spec SpecLeaf :: Spec -- | Modifiers (used for customizing constraints) SpecSelf :: Type -> Spec data SubSpec SubSpec :: SelSpec -> Type -> Type -> SubSpec data SelSpec NoSel :: SelSpec ConsSel :: Symbol -> SelSpec FieldSel :: Symbol -> SelSpec ConsFieldSel :: Symbol -> Symbol -> SelSpec type family Carrier ctag a :: Type type ToSpec tag (a :: Type) = 'SubSpec 'NoSel a (Carrier tag a) type ToSpecSel tag (s :: SelSpec) (a :: Type) = 'SubSpec s a (Carrier tag a) type family All (p :: k -> Constraint) (as :: [k]) :: Constraint type family AllMods (p :: Type -> Constraint) (as :: Spec) :: Constraint data GSubTag instance (GHC.Generics.Generic t, Control.MultiWalk.HasSub.HasSub' ctag (l : ls) 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing (GHC.Generics.Rep t)) => Control.MultiWalk.HasSub.HasSub ctag Control.MultiWalk.HasSub.GSubTag ('Control.MultiWalk.HasSub.SpecList (l : ls)) t instance (Control.MultiWalk.HasSub.Carrier ctag t1 GHC.Types.~ t2) => Control.MultiWalk.HasSub.HasSub' ctag ('Control.MultiWalk.HasSub.SubSpec 'Control.MultiWalk.HasSub.NoSel t1 t2 : ls) _a _b (GHC.Generics.K1 _c t2) instance (Control.MultiWalk.HasSub.Carrier ctag t1 GHC.Types.~ t2) => Control.MultiWalk.HasSub.HasSub' ctag ('Control.MultiWalk.HasSub.SubSpec ('Control.MultiWalk.HasSub.FieldSel s) t1 t2 : ls) _a ('GHC.Maybe.Just s) (GHC.Generics.K1 _c t2) instance (Control.MultiWalk.HasSub.Carrier ctag t1 GHC.Types.~ t2) => Control.MultiWalk.HasSub.HasSub' ctag ('Control.MultiWalk.HasSub.SubSpec ('Control.MultiWalk.HasSub.ConsSel s) t1 t2 : ls) ('GHC.Maybe.Just s) _b (GHC.Generics.K1 _c t2) instance (Control.MultiWalk.HasSub.Carrier ctag t1 GHC.Types.~ t2) => Control.MultiWalk.HasSub.HasSub' ctag ('Control.MultiWalk.HasSub.SubSpec ('Control.MultiWalk.HasSub.ConsFieldSel s1 s2) t1 t2 : ls) ('GHC.Maybe.Just s1) ('GHC.Maybe.Just s2) (GHC.Generics.K1 _c t2) instance Control.MultiWalk.HasSub.HasSub' ctag ls a b (GHC.Generics.K1 j s) => Control.MultiWalk.HasSub.HasSub' ctag (l : ls) a b (GHC.Generics.K1 j s) instance Control.MultiWalk.HasSub.HasSub' ctag '[] _a _b (GHC.Generics.K1 _c _d) instance (Control.MultiWalk.HasSub.HasSub' ctag s a 'GHC.Maybe.Nothing x, Control.MultiWalk.HasSub.HasSub' ctag s a 'GHC.Maybe.Nothing y) => Control.MultiWalk.HasSub.HasSub' ctag s a 'GHC.Maybe.Nothing (x GHC.Generics.:*: y) instance Control.MultiWalk.HasSub.HasSub' ctag _a _b _c GHC.Generics.U1 instance (Control.MultiWalk.HasSub.HasSub' ctag s 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing x, Control.MultiWalk.HasSub.HasSub' ctag s 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing y) => Control.MultiWalk.HasSub.HasSub' ctag s 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing (x GHC.Generics.:+: y) instance Control.MultiWalk.HasSub.HasSub' ctag ls a s x => Control.MultiWalk.HasSub.HasSub' ctag ls a 'GHC.Maybe.Nothing (GHC.Generics.S1 ('GHC.Generics.MetaSel s _a _b _c) x) instance Control.MultiWalk.HasSub.HasSub' ctag ls ('GHC.Maybe.Just s) 'GHC.Maybe.Nothing x => Control.MultiWalk.HasSub.HasSub' ctag ls 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing (GHC.Generics.C1 ('GHC.Generics.MetaCons s _a _b) x) instance Control.MultiWalk.HasSub.HasSub' ctag ls 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing x => Control.MultiWalk.HasSub.HasSub' ctag ls 'GHC.Maybe.Nothing 'GHC.Maybe.Nothing (GHC.Generics.D1 _a x) instance forall k tag s t (ctag :: k). (Control.MultiWalk.HasSub.Carrier tag s GHC.Types.~ t) => Control.MultiWalk.HasSub.HasSub tag ctag ('Control.MultiWalk.HasSub.SpecSelf s) t instance forall k tag (ctag :: k) t. Control.MultiWalk.HasSub.HasSub tag ctag 'Control.MultiWalk.HasSub.SpecLeaf t -- | This module contains the instances and definitions supporting -- Multiwalk module, along with the combinators for writing -- MultiSub instances. module Control.MultiWalk.Contains type family AllMods (p :: Type -> Constraint) (as :: Spec) :: Constraint type family All (p :: k -> Constraint) (as :: [k]) :: Constraint data GSubTag data SelSpec NoSel :: SelSpec ConsSel :: Symbol -> SelSpec FieldSel :: Symbol -> SelSpec ConsFieldSel :: Symbol -> Symbol -> SelSpec data SubSpec SubSpec :: SelSpec -> Type -> Type -> SubSpec data Spec SpecList :: [SubSpec] -> Spec SpecLeaf :: Spec -- | Modifiers (used for customizing constraints) SpecSelf :: Type -> Spec -- | 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. data Under (b :: Type) (s :: SelSpec) (a :: Type) -- | Use this for matching with another type that is coercible to the type -- you want. data MatchWith (s :: Type) (a :: Type) -- | Use this for matching with a type inside a traversable functor. data Trav (k :: Type -> Type) (a :: Type) -- | Auxiliary class that keeps track of how retrieve queries and walks -- from their lists and apply them according to the combinators. class TContains (fs :: [Type]) (t :: Type) tGetW :: (TContains fs t, Applicative m) => FList m fs -> ContainsCarrier t -> m (ContainsCarrier t) tGetQ :: (TContains fs t, Monoid m) => QList m fs -> ContainsCarrier t -> m class FContains (l :: [Type]) (t :: Type) fGet :: FContains l t => FList m l -> t -> m t fSet :: FContains l t => FList m l -> (t -> m t) -> FList m l -- | Heterogeneous list of monadic-valued functions data FList :: (Type -> Type) -> [Type] -> Type [FNil] :: FList m '[] [:.:] :: (x -> m x) -> FList m xs -> FList m (x : xs) infixr 8 :.: class QContains (l :: [Type]) (t :: Type) qGet :: QContains l t => QList m l -> t -> m qSet :: QContains l t => QList m l -> (t -> m) -> QList m l -- | Heterogeneous list of queries data QList :: Type -> [Type] -> Type [QNil] :: QList m '[] [:?:] :: (x -> m) -> QList m xs -> QList m (x : xs) infixr 8 :?: type ToSpecSel s a = ToSpecSel MWCTag s a type ToSpec a = ToSpec MWCTag a type Carrier a = Carrier MWCTag a type HasSub tag ls t = HasSub MWCTag tag ls t type family ContainsCarrier (a :: Type) :: Type data MWCTag -- | Modify (only) substructures by applying functions from FList. modSubWithFList :: forall tag ls t fs m. (HasSub tag ls t, Applicative m, AllMods (TContains fs) ls) => FList m fs -> t -> m t -- | Query (only) substructures by applying functions from QList. getSubWithQList :: forall tag ls t fs m. (HasSub tag ls t, Monoid m, AllMods (TContains fs) ls) => QList m fs -> t -> m instance (Control.MultiWalk.Contains.FContains fs (Control.MultiWalk.Contains.Carrier a), Control.MultiWalk.Contains.QContains fs (Control.MultiWalk.Contains.Carrier a)) => Control.MultiWalk.Contains.TContains fs a instance (Data.Traversable.Traversable f, Control.MultiWalk.Contains.TContains fs a) => Control.MultiWalk.Contains.TContains fs (Control.MultiWalk.Contains.Trav f a) instance (Control.MultiWalk.Contains.TContains fs a, GHC.Types.Coercible (Control.MultiWalk.Contains.Carrier a) s) => Control.MultiWalk.Contains.TContains fs (Control.MultiWalk.Contains.MatchWith s a) instance (Control.MultiWalk.Contains.TContains fs a, Control.MultiWalk.Contains.HasSub Control.MultiWalk.HasSub.GSubTag ('Control.MultiWalk.HasSub.SpecList '[ 'Control.MultiWalk.HasSub.SubSpec s a (Control.MultiWalk.Contains.Carrier a)]) b) => Control.MultiWalk.Contains.TContains fs (Control.MultiWalk.Contains.Under b s a) instance Control.MultiWalk.Contains.FContains (t : xs) t instance Control.MultiWalk.Contains.FContains xs t => Control.MultiWalk.Contains.FContains (x : xs) t instance Control.MultiWalk.Contains.QContains (t : xs) t instance Control.MultiWalk.Contains.QContains xs t => Control.MultiWalk.Contains.QContains (x : xs) t -- | This module provides functionality for recursively traversing and -- querying along multiple types. module Control.MultiWalk -- | You should instantiate MultiTag to a tag associated to the -- structure you are working with. The tag is mostly there to prevent -- orphan instances, since people are often working with structures from -- other packages (Pandoc AST, HTML, etc.) class (BuildF (MultiWalk' tag) (MultiTypes tag), BuildQ (MultiWalk' tag) (MultiTypes tag)) => MultiTag tag where { -- | The types that will be used in the walks and queries; every type -- listed here should have a MultiSub instance. (The compiler will -- complain about this.) type MultiTypes tag :: [Type]; } class MultiSub tag t where { -- | A list of substructure specifications for types that are substructures -- to this type; all types listed here should also be listed in the -- corresponding MultiTypes, but you can omit types from there -- that should not be regarded as subtypes. -- -- Substructure specifications are special datakinds that you can -- generate using ToSpec and ToSpecSel, and the combinators -- (eg. Under, MatchWith and Trav). type SubTypes tag t :: Spec; -- | If you want to write HasSub instances by hand (not that easy), you can -- put the associated HasSub tag here. Defaults to GSubTag (which -- derives Generic instances). type HasSubTag tag t :: Type; type HasSubTag tag t = GSubTag; } -- | Query a structure with a single query function (just like -- Pandoc.Walk). query :: forall tag m t a. (MultiTag tag, MultiWalk tag a, MultiWalk tag t, Monoid m) => (t -> m) -> a -> m -- | Modify a structure by walking with a single function (just like -- Pandoc.Walk). walk :: forall tag t c. (MultiTag tag, MultiWalk tag c, MultiWalk tag t) => (t -> t) -> c -> c -- | Modify a structure by walking with a single function (just like -- Pandoc.Walk). walkM :: forall tag t a m. (Monad m, MultiTag tag, MultiWalk tag a, MultiWalk tag t) => (t -> m t) -> a -> m a type Walk tag m = forall t. MultiWalk tag t => t -> m t type Query tag m = forall t. MultiWalk tag t => t -> m -- | Modify (only) substructures by applying functions from FList. walkSub :: forall tag t m. (Applicative m, MultiWalk tag t) => FList m (MultiTypes tag) -> t -> m t -- | Query (only) substructures by applying functions from QList. querySub :: forall tag t m. (Monoid m, MultiWalk tag t) => QList m (MultiTypes tag) -> t -> m -- | Most general way to create a walk. Create a walk with multiple -- functions, targeting multiple types. -- -- First argument is a function that takes a walk, an empty list of -- functions and should return a list of functions populated with the -- multiple walk functions. -- -- By "tying a knot", the first argument you are supplied with is almost -- the result of buildMultiW itself, the only difference being -- that it only walks substructures of the type. It's a -- responsability of each function in the FList to apply this -- function to its argument in any desired way, as to continue recursing -- down the "type tree". -- -- You can add functions to the empty FList via .>. -- --
--   multi :: Applicative m => Block -> m Block
--   multi = buildMultiW @PTag $ \sub list ->
--       list .> blks sub
--            .> inls sub
--     where
--       blks _ (CodeBlock _ c) = Para [Str c]
--       blks f x = f x
--       inls _ (Code _ c) = Str c
--       inls f x = f x
--   
buildMultiW :: forall tag m. (MultiTag tag, Applicative m) => (Walk tag m -> FList m (MultiTypes tag) -> FList m (MultiTypes tag)) -> Walk tag m -- | Most general way to create a query. Create a query with multiple -- functions, targeting multiple types. -- -- First argument is a function that takes a query, an empty list of -- queries and should return a list of queries populated with the -- multiple query functions. -- -- By "tying a knot", the first argument you are supplied with is almost -- the result of buildMultiQ itself, the only difference being -- that it only queries substructures of the type. It's a -- responsability of each function in the QList to apply this -- function to its argument in any desired way, as to continue recursing -- down the "type tree". -- -- You can add functions to the empty QList via ?>. -- --
--   multi :: Block -> [Text]
--   multi = buildMultiQ @PTag $ \sub list ->
--       list ?> blks sub
--            ?> inls sub
--     where
--       blks _ (CodeBlock _ c) = [c]
--       blks f x = f x
--       inls _ (Code _ c) = [c]
--       inls f x = f x
--   
buildMultiQ :: forall tag m. (MultiTag tag, Monoid m) => (Query tag m -> QList m (MultiTypes tag) -> QList m (MultiTypes tag)) -> Query tag m -- | Add a function to a FList. (.>) :: FContains ls t => FList m ls -> (t -> m t) -> FList m ls -- | Add a function to a QList. (?>) :: QContains ls t => QList m ls -> (t -> m) -> QList m ls type ToSpec a = ToSpec MWCTag a type ToSpecSel s a = ToSpecSel MWCTag s a data Spec SpecList :: [SubSpec] -> Spec SpecLeaf :: Spec -- | Modifiers (used for customizing constraints) SpecSelf :: Type -> Spec data SelSpec NoSel :: SelSpec ConsSel :: Symbol -> SelSpec FieldSel :: Symbol -> SelSpec ConsFieldSel :: Symbol -> Symbol -> SelSpec -- | Use this for matching with a type inside a traversable functor. data Trav (k :: Type -> Type) (a :: Type) -- | Use this for matching with another type that is coercible to the type -- you want. data MatchWith (s :: Type) (a :: Type) -- | 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. data Under (b :: Type) (s :: SelSpec) (a :: Type) type MultiWalk tag t = (AllMods (TContains (MultiTypes tag)) (SubTypes tag t), QContains (MultiTypes tag) t, FContains (MultiTypes tag) t, HasSub (HasSubTag tag t) (SubTypes tag t) t) -- | Heterogeneous list of monadic-valued functions data FList :: (Type -> Type) -> [Type] -> Type [FNil] :: FList m '[] [:.:] :: (x -> m x) -> FList m xs -> FList m (x : xs) infixr 8 :.: -- | Heterogeneous list of queries data QList :: Type -> [Type] -> Type [QNil] :: QList m '[] [:?:] :: (x -> m) -> QList m xs -> QList m (x : xs) infixr 8 :?: class All c ls => BuildF c ls buildF :: BuildF c ls => (forall t. c t => t -> m t) -> FList m ls class All c ls => BuildQ c ls buildQ :: BuildQ c ls => (forall t. c t => t -> m) -> QList m ls instance Control.MultiWalk.MultiWalk tag t => Control.MultiWalk.MultiWalk' tag t instance Control.MultiWalk.BuildF c '[] instance (Control.MultiWalk.BuildF c ls, c l) => Control.MultiWalk.BuildF c (l : ls) instance Control.MultiWalk.BuildQ c '[] instance (Control.MultiWalk.BuildQ c ls, c l) => Control.MultiWalk.BuildQ c (l : ls)