pandoc-lens-0.7.0: Lenses for Pandoc documents

Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Lens

Contents

Description

This provides a variety of optics for traversing and destructuring Pandoc documents.

Note that both Inline, Block, and MetaValue have Plated instances which are useful for traversing the AST.

Synopsis

Documents

data Pandoc #

Instances
Eq Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Pandoc -> Pandoc -> Bool #

(/=) :: Pandoc -> Pandoc -> Bool #

Data Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pandoc -> c Pandoc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pandoc #

toConstr :: Pandoc -> Constr #

dataTypeOf :: Pandoc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pandoc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc) #

gmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pandoc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pandoc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc #

Ord Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Read Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Show Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Generic Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Pandoc :: Type -> Type #

Methods

from :: Pandoc -> Rep Pandoc x #

to :: Rep Pandoc x -> Pandoc #

Semigroup Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Monoid Pandoc 
Instance details

Defined in Text.Pandoc.Definition

ToJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

NFData Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Pandoc -> () #

type Rep Pandoc 
Instance details

Defined in Text.Pandoc.Definition

type Rep Pandoc = D1 (MetaData "Pandoc" "Text.Pandoc.Definition" "pandoc-types-1.20-B6KLnpXHj8x8bBBaov9fsM" False) (C1 (MetaCons "Pandoc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Meta) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])))

body :: Lens' Pandoc [Block] Source #

The body of a pandoc document

meta :: Text -> Traversal' Pandoc MetaValue Source #

A traversal focusing on a particular metadata value of a document

Blocks

Prisms are provided for the constructors of Block as well as a Plated instance.

data Block #

Block element.

Instances
Eq Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Block -> Block -> Bool #

(/=) :: Block -> Block -> Bool #

Data Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block #

toConstr :: Block -> Constr #

dataTypeOf :: Block -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) #

gmapT :: (forall b. Data b => b -> b) -> Block -> Block #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block -> m Block #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block #

Ord Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

compare :: Block -> Block -> Ordering #

(<) :: Block -> Block -> Bool #

(<=) :: Block -> Block -> Bool #

(>) :: Block -> Block -> Bool #

(>=) :: Block -> Block -> Bool #

max :: Block -> Block -> Block #

min :: Block -> Block -> Block #

Read Block 
Instance details

Defined in Text.Pandoc.Definition

Show Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

ToJSON Block 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Block 
Instance details

Defined in Text.Pandoc.Definition

NFData Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Block -> () #

Plated Block Source # 
Instance details

Defined in Text.Pandoc.Lens

HasAttr Block Source # 
Instance details

Defined in Text.Pandoc.Lens

type Rep Block 
Instance details

Defined in Text.Pandoc.Definition

type Rep Block = D1 (MetaData "Block" "Text.Pandoc.Definition" "pandoc-types-1.20-B6KLnpXHj8x8bBBaov9fsM" False) (((C1 (MetaCons "Plain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: (C1 (MetaCons "Para" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "LineBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Inline]])))) :+: ((C1 (MetaCons "CodeBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "RawBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) :+: (C1 (MetaCons "BlockQuote" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "OrderedList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ListAttributes) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]]))))) :+: ((C1 (MetaCons "BulletList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]])) :+: (C1 (MetaCons "DefinitionList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([Inline], [[Block]])])) :+: C1 (MetaCons "Header" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))))) :+: ((C1 (MetaCons "HorizontalRule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Table" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Alignment])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TableCell]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[TableCell]]))))) :+: (C1 (MetaCons "Div" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "Null" PrefixI False) (U1 :: Type -> Type)))))

blockInlines :: Traversal' Block Inline Source #

Traverse over the Inline children of a Block

_Para :: Prism' Block [Inline] Source #

A prism on a paragraph Block

_CodeBlock :: Prism' Block Text Source #

A prism on the text of a CodeBlock

_OrderedList :: Prism' Block (ListAttributes, [[Block]]) Source #

A prism on the items of a bullet list Block

_BulletList :: Prism' Block [[Block]] Source #

A prism on the items of a bullet list Block

_DefinitionList :: Prism' Block [([Inline], [[Block]])] Source #

A prism on the items of a definition list Block

_Div :: Prism' Block [Block] Source #

A prism on a Div Block

_Null :: Prism' Block () Source #

A prism on a Null Block

Inlines

Prisms are provided for the constructors of Inline as well as a Plated instance.

data Inline #

Inline elements.

Instances
Eq Inline 
Instance details

Defined in Text.Pandoc.Definition

Methods

(==) :: Inline -> Inline -> Bool #

(/=) :: Inline -> Inline -> Bool #

Data Inline 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline #

toConstr :: Inline -> Constr #

dataTypeOf :: Inline -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) #

gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r #

gmapQ :: (forall d. Data d => d -> u) -> Inline -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Inline -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline #

Ord Inline 
Instance details

Defined in Text.Pandoc.Definition

Read Inline 
Instance details

Defined in Text.Pandoc.Definition

Show Inline 
Instance details

Defined in Text.Pandoc.Definition

Generic Inline 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

ToJSON Inline 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Inline 
Instance details

Defined in Text.Pandoc.Definition

NFData Inline 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Inline -> () #

Plated Inline Source # 
Instance details

Defined in Text.Pandoc.Lens

HasAttr Inline Source # 
Instance details

Defined in Text.Pandoc.Lens

type Rep Inline 
Instance details

Defined in Text.Pandoc.Definition

type Rep Inline = D1 (MetaData "Inline" "Text.Pandoc.Definition" "pandoc-types-1.20-B6KLnpXHj8x8bBBaov9fsM" False) ((((C1 (MetaCons "Str" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "Emph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))) :+: (C1 (MetaCons "Strong" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Strikeout" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))) :+: ((C1 (MetaCons "Superscript" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Subscript" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))) :+: (C1 (MetaCons "SmallCaps" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: (C1 (MetaCons "Quoted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "Cite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Citation]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))))) :+: (((C1 (MetaCons "Code" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "Space" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SoftBreak" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LineBreak" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Math" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MathType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))) :+: ((C1 (MetaCons "RawInline" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "Link" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Target)))) :+: (C1 (MetaCons "Image" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Target))) :+: (C1 (MetaCons "Note" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "Span" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))))))

_Code :: Prism' Inline Text Source #

A prism on the body of a Code Inline

_Space :: Prism' Inline () Source #

A prism on a Space Inline

inlinePrePlate :: Traversal' Inline [Inline] Source #

An affine traversal over the '[Inline]' in the last argument of an Inline constructor

Metadata

Prisms are provided for the constructors of MetaValue as well as a Plated instance.

data MetaValue #

Instances
Eq MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Data MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetaValue -> c MetaValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetaValue #

toConstr :: MetaValue -> Constr #

dataTypeOf :: MetaValue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetaValue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue) #

gmapT :: (forall b. Data b => b -> b) -> MetaValue -> MetaValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetaValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetaValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaValue -> m MetaValue #

Ord MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Read MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Show MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Generic MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep MetaValue :: Type -> Type #

ToJSON MetaValue 
Instance details

Defined in Text.Pandoc.Definition

FromJSON MetaValue 
Instance details

Defined in Text.Pandoc.Definition

NFData MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: MetaValue -> () #

Plated MetaValue Source # 
Instance details

Defined in Text.Pandoc.Lens

type Rep MetaValue 
Instance details

Defined in Text.Pandoc.Definition

_MetaMap :: Prism' MetaValue (Map Text MetaValue) Source #

A prism on a piece of MetaMap metadata

_MetaList :: Prism' MetaValue [MetaValue] Source #

A prism on a piece of MetaList metadata

_MetaBool :: Prism' MetaValue Bool Source #

A prism on a piece of MetaBool metadata

_MetaString :: Prism' MetaValue Text Source #

A prism on a piece of MetaString metadata

_MetaInlines :: Prism' MetaValue [Inline] Source #

A prism on a piece of MetaInlines metadata

_MetaBlocks :: Prism' MetaValue [Block] Source #

A prism on a piece of MetaBlocks metadata

Attributes

class HasAttr a where Source #

An object that has attributes

Methods

attributes :: Traversal' a Attr Source #

A traversal over the attributes of an object

Instances
HasAttr Block Source # 
Instance details

Defined in Text.Pandoc.Lens

HasAttr Inline Source # 
Instance details

Defined in Text.Pandoc.Lens

attrIdentifier :: Lens' Attr Text Source #

A lens onto identifier of an Attr

attrClasses :: Lens' Attr [Text] Source #

A lens onto classes of an Attr

attrs :: Lens' Attr [(Text, Text)] Source #

A lens onto the key-value pairs of an Attr

Orphan instances

Ixed Meta Source # 
Instance details

At Meta Source # 
Instance details

Methods

at :: Index Meta -> Lens' Meta (Maybe (IxValue Meta)) #

Plated MetaValue Source # 
Instance details

Plated Block Source # 
Instance details

Plated Inline Source # 
Instance details

Wrapped Meta Source # 
Instance details

Associated Types

type Unwrapped Meta :: Type #