Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 ([Inline], [Alignment], [Double], [TableCell], [[TableCell]])
- _Div :: Prism' Block [Block]
- _Null :: Prism' 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
Eq Pandoc | |
Data Pandoc | |
Defined in Text.Pandoc.Definition 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 | |
Read Pandoc | |
Show Pandoc | |
Generic Pandoc | |
Semigroup Pandoc | |
Monoid Pandoc | |
ToJSON Pandoc | |
Defined in Text.Pandoc.Definition | |
FromJSON Pandoc | |
NFData Pandoc | |
Defined in Text.Pandoc.Definition | |
type Rep Pandoc | |
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]))) |
meta :: Text -> Traversal' Pandoc MetaValue Source #
A traversal focusing on a particular metadata value of a document
Blocks
Block element.
Instances
_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
Inlines
Inline elements.
Instances
_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
_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
attributes :: Traversal' a Attr Source #
A traversal over the attributes of an object
Instances
HasAttr Block Source # | |
Defined in Text.Pandoc.Lens | |
HasAttr Inline Source # | |
Defined in Text.Pandoc.Lens |