pandoc-lens-0.8.0: Lenses for Pandoc documents
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Lens

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

Instances details
FromJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

ToJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

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 :: forall r r'. (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 #

Monoid Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Semigroup Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Generic Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Pandoc 
Instance details

Defined in Text.Pandoc.Definition

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

Methods

from :: Pandoc -> Rep Pandoc x #

to :: Rep Pandoc x -> Pandoc #

Read Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Show Pandoc 
Instance details

Defined in Text.Pandoc.Definition

NFData Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Pandoc -> () #

Eq Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

Ord Pandoc 
Instance details

Defined in Text.Pandoc.Definition

HasMeta Pandoc 
Instance details

Defined in Text.Pandoc.Builder

Methods

setMeta :: ToMetaValue b => Text -> b -> Pandoc -> Pandoc #

deleteMeta :: Text -> Pandoc -> Pandoc #

Walkable Block Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Pandoc -> m Pandoc #

query :: Monoid c => (Block -> c) -> Pandoc -> c #

Walkable Inline Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Pandoc -> m Pandoc #

query :: Monoid c => (Inline -> c) -> Pandoc -> c #

Walkable Meta Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Meta -> Meta) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Meta -> m Meta) -> Pandoc -> m Pandoc #

query :: Monoid c => (Meta -> c) -> Pandoc -> c #

Walkable MetaValue Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (MetaValue -> MetaValue) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (MetaValue -> m MetaValue) -> Pandoc -> m Pandoc #

query :: Monoid c => (MetaValue -> c) -> Pandoc -> c #

Walkable Pandoc Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Pandoc -> Pandoc) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc #

query :: Monoid c => (Pandoc -> c) -> Pandoc -> c #

Walkable [Block] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Block] -> c) -> Pandoc -> c #

Walkable [Inline] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Inline] -> c) -> Pandoc -> c #

type Rep Pandoc 
Instance details

Defined in Text.Pandoc.Definition

type Rep Pandoc = D1 ('MetaData "Pandoc" "Text.Pandoc.Definition" "pandoc-types-1.23.1-8pfFxbwBHDP7buvpNafhrr" 'False) (C1 ('MetaCons "Pandoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Meta) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (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

Instances details
FromJSON Block 
Instance details

Defined in Text.Pandoc.Definition

ToJSON Block 
Instance details

Defined in Text.Pandoc.Definition

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 :: 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 
Instance details

Defined in Text.Pandoc.Builder

Semigroup Blocks 
Instance details

Defined in Text.Pandoc.Builder

Generic Block 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Block 
Instance details

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]))))))

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> 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 #

NFData Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Block -> () #

Eq Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

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 #

Plated Block Source # 
Instance details

Defined in Text.Pandoc.Lens

HasAttr Block Source # 
Instance details

Defined in Text.Pandoc.Lens

ToMetaValue Blocks 
Instance details

Defined in Text.Pandoc.Builder

Walkable Block Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Block -> m Block #

query :: Monoid c => (Block -> c) -> Block -> c #

Walkable Block Caption 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Caption -> Caption #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Caption -> m Caption #

query :: Monoid c => (Block -> c) -> Caption -> c #

Walkable Block Cell 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Cell -> Cell #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Cell -> m Cell #

query :: Monoid c => (Block -> c) -> Cell -> c #

Walkable Block Citation 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Citation -> Citation #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Citation -> m Citation #

query :: Monoid c => (Block -> c) -> Citation -> c #

Walkable Block Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Inline -> m Inline #

query :: Monoid c => (Block -> c) -> Inline -> c #

Walkable Block Meta 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Meta -> Meta #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Meta -> m Meta #

query :: Monoid c => (Block -> c) -> Meta -> c #

Walkable Block MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> MetaValue -> m MetaValue #

query :: Monoid c => (Block -> c) -> MetaValue -> c #

Walkable Block Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Pandoc -> m Pandoc #

query :: Monoid c => (Block -> c) -> Pandoc -> c #

Walkable Block Row 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Row -> Row #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Row -> m Row #

query :: Monoid c => (Block -> c) -> Row -> c #

Walkable Block TableBody 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> TableBody -> TableBody #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> TableBody -> m TableBody #

query :: Monoid c => (Block -> c) -> TableBody -> c #

Walkable Block TableFoot 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> TableFoot -> TableFoot #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> TableFoot -> m TableFoot #

query :: Monoid c => (Block -> c) -> TableFoot -> c #

Walkable Block TableHead 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> TableHead -> TableHead #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> TableHead -> m TableHead #

query :: Monoid c => (Block -> c) -> TableHead -> c #

Walkable Inline Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Block -> m Block #

query :: Monoid c => (Inline -> c) -> Block -> c #

Walkable [Block] Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Block -> m Block #

query :: Monoid c => ([Block] -> c) -> Block -> c #

Walkable [Block] Caption 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Caption -> Caption #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Caption -> m Caption #

query :: Monoid c => ([Block] -> c) -> Caption -> c #

Walkable [Block] Cell 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Cell -> Cell #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Cell -> m Cell #

query :: Monoid c => ([Block] -> c) -> Cell -> c #

Walkable [Block] Citation 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Citation -> Citation #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Citation -> m Citation #

query :: Monoid c => ([Block] -> c) -> Citation -> c #

Walkable [Block] Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Inline -> m Inline #

query :: Monoid c => ([Block] -> c) -> Inline -> c #

Walkable [Block] Meta 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Meta -> Meta #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Meta -> m Meta #

query :: Monoid c => ([Block] -> c) -> Meta -> c #

Walkable [Block] MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> MetaValue -> m MetaValue #

query :: Monoid c => ([Block] -> c) -> MetaValue -> c #

Walkable [Block] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Block] -> c) -> Pandoc -> c #

Walkable [Block] Row 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Row -> Row #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Row -> m Row #

query :: Monoid c => ([Block] -> c) -> Row -> c #

Walkable [Block] TableBody 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> TableBody -> TableBody #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> TableBody -> m TableBody #

query :: Monoid c => ([Block] -> c) -> TableBody -> c #

Walkable [Block] TableFoot 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> TableFoot -> TableFoot #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> TableFoot -> m TableFoot #

query :: Monoid c => ([Block] -> c) -> TableFoot -> c #

Walkable [Block] TableHead 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> TableHead -> TableHead #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> TableHead -> m TableHead #

query :: Monoid c => ([Block] -> c) -> TableHead -> c #

Walkable [Inline] Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Block -> m Block #

query :: Monoid c => ([Inline] -> c) -> Block -> c #

Walkable [Block] [Block] 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> [Block] -> [Block] #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> [Block] -> m [Block] #

query :: Monoid c => ([Block] -> c) -> [Block] -> c #

type Rep Block 
Instance details

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]))))))

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

blockPrePlate :: Traversal' Block [Block] Source #

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

Inlines

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

data Inline #

Inline elements.

Instances

Instances details
FromJSON Inline 
Instance details

Defined in Text.Pandoc.Definition

ToJSON Inline 
Instance details

Defined in Text.Pandoc.Definition

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 :: 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 
Instance details

Defined in Text.Pandoc.Builder

Methods

fromString :: String -> Inlines #

Monoid Inlines 
Instance details

Defined in Text.Pandoc.Builder

Semigroup Inlines 
Instance details

Defined in Text.Pandoc.Builder

Generic Inline 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Inline 
Instance details

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])))))))

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Read Inline 
Instance details

Defined in Text.Pandoc.Definition

Show Inline 
Instance details

Defined in Text.Pandoc.Definition

NFData Inline 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Inline -> () #

Eq Inline 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

Ord Inline 
Instance details

Defined in Text.Pandoc.Definition

Plated Inline Source # 
Instance details

Defined in Text.Pandoc.Lens

HasAttr Inline Source # 
Instance details

Defined in Text.Pandoc.Lens

ToMetaValue Inlines 
Instance details

Defined in Text.Pandoc.Builder

Walkable Block Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Inline -> m Inline #

query :: Monoid c => (Block -> c) -> Inline -> c #

Walkable Inline Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Block -> m Block #

query :: Monoid c => (Inline -> c) -> Block -> c #

Walkable Inline Caption 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Caption -> Caption #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Caption -> m Caption #

query :: Monoid c => (Inline -> c) -> Caption -> c #

Walkable Inline Cell 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Cell -> Cell #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Cell -> m Cell #

query :: Monoid c => (Inline -> c) -> Cell -> c #

Walkable Inline Citation 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Citation -> Citation #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Citation -> m Citation #

query :: Monoid c => (Inline -> c) -> Citation -> c #

Walkable Inline Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Inline -> m Inline #

query :: Monoid c => (Inline -> c) -> Inline -> c #

Walkable Inline Meta 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Meta -> Meta #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Meta -> m Meta #

query :: Monoid c => (Inline -> c) -> Meta -> c #

Walkable Inline MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> MetaValue -> m MetaValue #

query :: Monoid c => (Inline -> c) -> MetaValue -> c #

Walkable Inline Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Pandoc -> m Pandoc #

query :: Monoid c => (Inline -> c) -> Pandoc -> c #

Walkable Inline Row 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Row -> Row #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Row -> m Row #

query :: Monoid c => (Inline -> c) -> Row -> c #

Walkable Inline TableBody 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> TableBody -> TableBody #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> TableBody -> m TableBody #

query :: Monoid c => (Inline -> c) -> TableBody -> c #

Walkable Inline TableFoot 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> TableFoot -> TableFoot #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> TableFoot -> m TableFoot #

query :: Monoid c => (Inline -> c) -> TableFoot -> c #

Walkable Inline TableHead 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> TableHead -> TableHead #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> TableHead -> m TableHead #

query :: Monoid c => (Inline -> c) -> TableHead -> c #

Walkable [Block] Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Inline -> m Inline #

query :: Monoid c => ([Block] -> c) -> Inline -> c #

Walkable [Inline] Block 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Block -> Block #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Block -> m Block #

query :: Monoid c => ([Inline] -> c) -> Block -> c #

Walkable [Inline] Caption 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Caption -> Caption #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Caption -> m Caption #

query :: Monoid c => ([Inline] -> c) -> Caption -> c #

Walkable [Inline] Cell 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Cell -> Cell #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Cell -> m Cell #

query :: Monoid c => ([Inline] -> c) -> Cell -> c #

Walkable [Inline] Citation 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Citation -> Citation #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Citation -> m Citation #

query :: Monoid c => ([Inline] -> c) -> Citation -> c #

Walkable [Inline] Inline 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Inline -> Inline #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Inline -> m Inline #

query :: Monoid c => ([Inline] -> c) -> Inline -> c #

Walkable [Inline] Meta 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Meta -> Meta #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Meta -> m Meta #

query :: Monoid c => ([Inline] -> c) -> Meta -> c #

Walkable [Inline] MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> MetaValue -> m MetaValue #

query :: Monoid c => ([Inline] -> c) -> MetaValue -> c #

Walkable [Inline] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Inline] -> c) -> Pandoc -> c #

Walkable [Inline] Row 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Row -> Row #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Row -> m Row #

query :: Monoid c => ([Inline] -> c) -> Row -> c #

Walkable [Inline] TableBody 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> TableBody -> TableBody #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> TableBody -> m TableBody #

query :: Monoid c => ([Inline] -> c) -> TableBody -> c #

Walkable [Inline] TableFoot 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> TableFoot -> TableFoot #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> TableFoot -> m TableFoot #

query :: Monoid c => ([Inline] -> c) -> TableFoot -> c #

Walkable [Inline] TableHead 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> TableHead -> TableHead #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> TableHead -> m TableHead #

query :: Monoid c => ([Inline] -> c) -> TableHead -> c #

Walkable [Inline] [Inline] 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> [Inline] -> [Inline] #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> [Inline] -> m [Inline] #

query :: Monoid c => ([Inline] -> c) -> [Inline] -> c #

type Rep Inline 
Instance details

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])))))))

_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

Instances details
FromJSON MetaValue 
Instance details

Defined in Text.Pandoc.Definition

ToJSON 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 :: 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 
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

NFData MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: MetaValue -> () #

Eq MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Ord MetaValue 
Instance details

Defined in Text.Pandoc.Definition

Plated MetaValue Source # 
Instance details

Defined in Text.Pandoc.Lens

ToMetaValue MetaValue 
Instance details

Defined in Text.Pandoc.Builder

Walkable Block MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> MetaValue -> m MetaValue #

query :: Monoid c => (Block -> c) -> MetaValue -> c #

Walkable Inline MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> MetaValue -> m MetaValue #

query :: Monoid c => (Inline -> c) -> MetaValue -> c #

Walkable MetaValue Meta 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (MetaValue -> MetaValue) -> Meta -> Meta #

walkM :: (Monad m, Applicative m, Functor m) => (MetaValue -> m MetaValue) -> Meta -> m Meta #

query :: Monoid c => (MetaValue -> c) -> Meta -> c #

Walkable MetaValue MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (MetaValue -> MetaValue) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => (MetaValue -> m MetaValue) -> MetaValue -> m MetaValue #

query :: Monoid c => (MetaValue -> c) -> MetaValue -> c #

Walkable MetaValue Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (MetaValue -> MetaValue) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (MetaValue -> m MetaValue) -> Pandoc -> m Pandoc #

query :: Monoid c => (MetaValue -> c) -> Pandoc -> c #

Walkable [Block] MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> MetaValue -> m MetaValue #

query :: Monoid c => ([Block] -> c) -> MetaValue -> c #

Walkable [Inline] MetaValue 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> MetaValue -> MetaValue #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> MetaValue -> m MetaValue #

query :: Monoid c => ([Inline] -> c) -> MetaValue -> c #

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

Instances details
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

At Meta Source # 
Instance details

Methods

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

Ixed Meta Source # 
Instance details

Plated Block Source # 
Instance details

Plated Inline Source # 
Instance details

Plated MetaValue Source # 
Instance details

Wrapped Meta Source # 
Instance details

Associated Types

type Unwrapped Meta 
Instance details

Defined in Text.Pandoc.Lens