Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Pandoc.Lens
Description
Synopsis
- data Pandoc
- body :: Lens' Pandoc [Block]
- meta :: Text -> Traversal' Pandoc MetaValue
- data Block
- blockInlines :: Traversal' Block Inline
- _Plain :: Prism' Block [Inline]
- _Para :: Prism' Block [Inline]
- _CodeBlock :: Prism' Block Text
- _BlockQuote :: Prism' Block [Block]
- _OrderedList :: Prism' Block (ListAttributes, [[Block]])
- _BulletList :: Prism' Block [[Block]]
- _DefinitionList :: Prism' Block [([Inline], [[Block]])]
- _Header :: Prism' Block (Int, [Inline])
- _HorizontalRule :: Prism' Block ()
- _Table :: Prism' Block (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot)
- _Div :: Prism' Block [Block]
- blockPrePlate :: Traversal' Block [Block]
- data Inline
- _Str :: Prism' Inline Text
- _Emph :: Prism' Inline [Inline]
- _Strong :: Prism' Inline [Inline]
- _Strikeout :: Prism' Inline [Inline]
- _Superscript :: Prism' Inline [Inline]
- _Subscript :: Prism' Inline [Inline]
- _SmallCaps :: Prism' Inline [Inline]
- _Quoted :: Prism' Inline (QuoteType, [Inline])
- _Cite :: Prism' Inline ([Citation], [Inline])
- _Code :: Prism' Inline Text
- _Space :: Prism' Inline ()
- _LineBreak :: Prism' Inline ()
- _Math :: Prism' Inline (MathType, Text)
- _RawInline :: Prism' Inline (Format, Text)
- _Link :: Prism' Inline ([Inline], Target)
- _Image :: Prism' Inline ([Inline], Target)
- _Note :: Prism' Inline [Block]
- _Span :: Prism' Inline [Inline]
- inlinePrePlate :: Traversal' Inline [Inline]
- data MetaValue
- _MetaMap :: Prism' MetaValue (Map Text MetaValue)
- _MetaList :: Prism' MetaValue [MetaValue]
- _MetaBool :: Prism' MetaValue Bool
- _MetaString :: Prism' MetaValue Text
- _MetaInlines :: Prism' MetaValue [Inline]
- _MetaBlocks :: Prism' MetaValue [Block]
- class HasAttr a where
- attributes :: Traversal' a Attr
- attrIdentifier :: Lens' Attr Text
- attrClasses :: Lens' Attr [Text]
- attrs :: Lens' Attr [(Text, Text)]
Documents
Instances
meta :: Text -> Traversal' Pandoc MetaValue Source #
A traversal focusing on a particular metadata value of a document
Blocks
Block element.
Instances
FromJSON Block | |||||
Defined in Text.Pandoc.Definition | |||||
ToJSON Block | |||||
Data Block | |||||
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 # 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 :: forall r r'. (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 # | |||||
Monoid Blocks | |||||
Semigroup Blocks | |||||
Generic Block | |||||
Defined in Text.Pandoc.Definition Associated Types
| |||||
Read Block | |||||
Show Block | |||||
NFData Block | |||||
Defined in Text.Pandoc.Definition | |||||
Eq Block | |||||
Ord Block | |||||
Plated Block Source # | |||||
Defined in Text.Pandoc.Lens Methods plate :: Traversal' Block Block # | |||||
HasAttr Block Source # | |||||
Defined in Text.Pandoc.Lens Methods | |||||
ToMetaValue Blocks | |||||
Defined in Text.Pandoc.Builder Methods toMetaValue :: Blocks -> MetaValue # | |||||
Walkable Block Block | |||||
Walkable Block Caption | |||||
Walkable Block Cell | |||||
Walkable Block Citation | |||||
Walkable Block Inline | |||||
Walkable Block Meta | |||||
Walkable Block MetaValue | |||||
Walkable Block Pandoc | |||||
Walkable Block Row | |||||
Walkable Block TableBody | |||||
Walkable Block TableFoot | |||||
Walkable Block TableHead | |||||
Walkable Inline Block | |||||
Walkable [Block] Block | |||||
Walkable [Block] Caption | |||||
Walkable [Block] Cell | |||||
Walkable [Block] Citation | |||||
Walkable [Block] Inline | |||||
Walkable [Block] Meta | |||||
Walkable [Block] MetaValue | |||||
Walkable [Block] Pandoc | |||||
Walkable [Block] Row | |||||
Walkable [Block] TableBody | |||||
Walkable [Block] TableFoot | |||||
Walkable [Block] TableHead | |||||
Walkable [Inline] Block | |||||
Walkable [Block] [Block] | |||||
type Rep Block | |||||
Defined in Text.Pandoc.Definition type Rep Block = D1 ('MetaData "Block" "Text.Pandoc.Definition" "pandoc-types-1.23.1-8pfFxbwBHDP7buvpNafhrr" 'False) (((C1 ('MetaCons "Plain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: (C1 ('MetaCons "Para" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: C1 ('MetaCons "LineBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [[Inline]])))) :+: ((C1 ('MetaCons "CodeBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "RawBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "BlockQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Block])) :+: C1 ('MetaCons "OrderedList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ListAttributes) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [[Block]]))))) :+: ((C1 ('MetaCons "BulletList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [[Block]])) :+: (C1 ('MetaCons "DefinitionList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [([Inline], [[Block]])])) :+: C1 ('MetaCons "Header" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]))))) :+: ((C1 ('MetaCons "HorizontalRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Table" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Caption) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ColSpec]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableHead) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TableBody]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableFoot))))) :+: (C1 ('MetaCons "Figure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Caption) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Block]))) :+: C1 ('MetaCons "Div" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Block])))))) |
_BlockQuote :: Prism' Block [Block] Source #
A prism on a BlockQuote
_OrderedList :: Prism' Block (ListAttributes, [[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
_HorizontalRule :: Prism' Block () Source #
A prism on a HorizontalRule
Block
blockPrePlate :: Traversal' Block [Block] Source #
An affine traversal over the '[Block]' in the last argument of an Block
constructor
Inlines
Inline elements.
Instances
FromJSON Inline | |||||
Defined in Text.Pandoc.Definition | |||||
ToJSON Inline | |||||
Data Inline | |||||
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 :: forall r r'. (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 # | |||||
IsString Inlines | |||||
Defined in Text.Pandoc.Builder Methods fromString :: String -> Inlines # | |||||
Monoid Inlines | |||||
Semigroup Inlines | |||||
Generic Inline | |||||
Defined in Text.Pandoc.Definition Associated Types
| |||||
Read Inline | |||||
Show Inline | |||||
NFData Inline | |||||
Defined in Text.Pandoc.Definition | |||||
Eq Inline | |||||
Ord Inline | |||||
Plated Inline Source # | |||||
Defined in Text.Pandoc.Lens Methods plate :: Traversal' Inline Inline # | |||||
HasAttr Inline Source # | |||||
Defined in Text.Pandoc.Lens Methods | |||||
ToMetaValue Inlines | |||||
Defined in Text.Pandoc.Builder Methods toMetaValue :: Inlines -> MetaValue # | |||||
Walkable Block Inline | |||||
Walkable Inline Block | |||||
Walkable Inline Caption | |||||
Walkable Inline Cell | |||||
Walkable Inline Citation | |||||
Walkable Inline Inline | |||||
Walkable Inline Meta | |||||
Walkable Inline MetaValue | |||||
Walkable Inline Pandoc | |||||
Walkable Inline Row | |||||
Walkable Inline TableBody | |||||
Walkable Inline TableFoot | |||||
Walkable Inline TableHead | |||||
Walkable [Block] Inline | |||||
Walkable [Inline] Block | |||||
Walkable [Inline] Caption | |||||
Walkable [Inline] Cell | |||||
Walkable [Inline] Citation | |||||
Walkable [Inline] Inline | |||||
Walkable [Inline] Meta | |||||
Walkable [Inline] MetaValue | |||||
Walkable [Inline] Pandoc | |||||
Walkable [Inline] Row | |||||
Walkable [Inline] TableBody | |||||
Walkable [Inline] TableFoot | |||||
Walkable [Inline] TableHead | |||||
Walkable [Inline] [Inline] | |||||
type Rep Inline | |||||
Defined in Text.Pandoc.Definition type Rep Inline = D1 ('MetaData "Inline" "Text.Pandoc.Definition" "pandoc-types-1.23.1-8pfFxbwBHDP7buvpNafhrr" 'False) ((((C1 ('MetaCons "Str" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Emph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]))) :+: (C1 ('MetaCons "Underline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: (C1 ('MetaCons "Strong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: C1 ('MetaCons "Strikeout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]))))) :+: ((C1 ('MetaCons "Superscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: C1 ('MetaCons "Subscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]))) :+: (C1 ('MetaCons "SmallCaps" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: (C1 ('MetaCons "Quoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QuoteType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: C1 ('MetaCons "Cite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Citation]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])))))) :+: (((C1 ('MetaCons "Code" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (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 'DecidedStrict) (Rec0 MathType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))) :+: ((C1 ('MetaCons "RawInline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Link" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Target)))) :+: (C1 ('MetaCons "Image" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Target))) :+: (C1 ('MetaCons "Note" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Block])) :+: C1 ('MetaCons "Span" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline]))))))) |
_Superscript :: Prism' Inline [Inline] Source #
A prism on a Superscript
Inline
inlinePrePlate :: Traversal' Inline [Inline] Source #
An affine traversal over the '[Inline]' in the last argument of an Inline
constructor
Metadata
Instances
FromJSON MetaValue | |||||
Defined in Text.Pandoc.Definition | |||||
ToJSON MetaValue | |||||
Data MetaValue | |||||
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 :: forall r r'. (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 # | |||||
Generic MetaValue | |||||
Defined in Text.Pandoc.Definition Associated Types
| |||||
Read MetaValue | |||||
Show MetaValue | |||||
NFData MetaValue | |||||
Defined in Text.Pandoc.Definition | |||||
Eq MetaValue | |||||
Ord MetaValue | |||||
Plated MetaValue Source # | |||||
Defined in Text.Pandoc.Lens Methods | |||||
ToMetaValue MetaValue | |||||
Defined in Text.Pandoc.Builder Methods toMetaValue :: MetaValue -> MetaValue # | |||||
Walkable Block MetaValue | |||||
Walkable Inline MetaValue | |||||
Walkable MetaValue Meta | |||||
Walkable MetaValue MetaValue | |||||
Walkable MetaValue Pandoc | |||||
Walkable [Block] MetaValue | |||||
Walkable [Inline] MetaValue | |||||
type Rep MetaValue | |||||
Defined in Text.Pandoc.Definition type Rep MetaValue = D1 ('MetaData "MetaValue" "Text.Pandoc.Definition" "pandoc-types-1.23.1-8pfFxbwBHDP7buvpNafhrr" 'False) ((C1 ('MetaCons "MetaMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Text MetaValue))) :+: (C1 ('MetaCons "MetaList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [MetaValue])) :+: C1 ('MetaCons "MetaBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))) :+: (C1 ('MetaCons "MetaString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "MetaInlines" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Inline])) :+: C1 ('MetaCons "MetaBlocks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Block]))))) |
_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
Instances
HasAttr Block Source # | |
Defined in Text.Pandoc.Lens Methods | |
HasAttr Inline Source # | |
Defined in Text.Pandoc.Lens Methods |