pandoc-3.1.6: Conversion between markup formats
CopyrightCopyright (C) 2007 Galois Inc. 2021-2023 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.XML.Light.Types

Description

This code is taken from xml-light, released under the BSD3 license. It has been modified to use Text instead of String, and the fromXL* functions have been added.

Synopsis

Basic types, duplicating those from xml-light but with Text

type Line = Integer Source #

A line is an Integer

data Content Source #

XML content

Constructors

Elem Element 
Text CData 
CRef Text 

Instances

Instances details
Data Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: Content -> Constr #

dataTypeOf :: Content -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Eq Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

Ord Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Node Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Content -> Element Source #

Node [Content] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Content] -> Element Source #

Node (Attr, Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Content) -> Element Source #

Node ([Attr], Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Content) -> Element Source #

Node ([Attr], [Content]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Content]) -> Element Source #

data Element Source #

XML elements

Constructors

Element 

Instances

Instances details
Data Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Eq Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

Ord Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Node Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Element -> Element Source #

Node [Element] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Element] -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Element) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

data Attr Source #

XML attributes

Constructors

Attr 

Fields

Instances

Instances details
Data Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: Attr -> Constr #

dataTypeOf :: Attr -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Eq Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

Ord Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

compare :: Attr -> Attr -> Ordering #

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

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

(>) :: Attr -> Attr -> Bool #

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

max :: Attr -> Attr -> Attr #

min :: Attr -> Attr -> Attr #

Node Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Attr -> Element Source #

Node [Attr] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Attr] -> Element Source #

Node (Attr, CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, CData) -> Element Source #

Node (Attr, Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Content) -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Element) -> Element Source #

Node (Attr, Text) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Text) -> Element Source #

Node ([Attr], CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], CData) -> Element Source #

Node ([Attr], Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Content) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node ([Attr], Text) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Text) -> Element Source #

Node ([Attr], [CData]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [CData]) -> Element Source #

Node ([Attr], [Content]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Content]) -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

data CData Source #

XML CData

Constructors

CData 

Instances

Instances details
Data CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: CData -> Constr #

dataTypeOf :: CData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

showsPrec :: Int -> CData -> ShowS #

show :: CData -> String #

showList :: [CData] -> ShowS #

Eq CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

Ord CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

compare :: CData -> CData -> Ordering #

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

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

(>) :: CData -> CData -> Bool #

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

max :: CData -> CData -> CData #

min :: CData -> CData -> CData #

Node CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> CData -> Element Source #

Node [CData] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [CData] -> Element Source #

Node (Attr, CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, CData) -> Element Source #

Node ([Attr], CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], CData) -> Element Source #

Node ([Attr], [CData]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [CData]) -> Element Source #

data CDataKind Source #

Constructors

CDataText

Ordinary character data; pretty printer escapes &, < etc.

CDataVerbatim

Unescaped character data; pretty printer embeds it in <![CDATA[..

CDataRaw

As-is character data; pretty printer passes it along without any escaping or CDATA wrap-up.

Instances

Instances details
Data CDataKind Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: CDataKind -> Constr #

dataTypeOf :: CDataKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CDataKind Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Eq CDataKind Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Ord CDataKind Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

data QName Source #

XML qualified names

Constructors

QName 

Fields

Instances

Instances details
Data QName Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

toConstr :: QName -> Constr #

dataTypeOf :: QName -> DataType #

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

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

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

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

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

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

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

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

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

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

Show QName Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

showsPrec :: Int -> QName -> ShowS #

show :: QName -> String #

showList :: [QName] -> ShowS #

Eq QName Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

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

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

Ord QName Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

compare :: QName -> QName -> Ordering #

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

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

(>) :: QName -> QName -> Bool #

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

max :: QName -> QName -> QName #

min :: QName -> QName -> QName #

class Node t where Source #

Methods

node :: QName -> t -> Element Source #

Instances

Instances details
Node Attr Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Attr -> Element Source #

Node CData Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> CData -> Element Source #

Node Content Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Content -> Element Source #

Node Element Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Element -> Element Source #

Node Text Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> Text -> Element Source #

Node () Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> () -> Element Source #

Node [Attr] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Attr] -> Element Source #

Node [CData] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [CData] -> Element Source #

Node [Content] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Content] -> Element Source #

Node [Element] Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> [Element] -> Element Source #

Node (Attr, CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, CData) -> Element Source #

Node (Attr, Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Content) -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Element) -> Element Source #

Node (Attr, Text) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> (Attr, Text) -> Element Source #

Node ([Attr], CData) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], CData) -> Element Source #

Node ([Attr], Content) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Content) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node ([Attr], Text) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], Text) -> Element Source #

Node ([Attr], [CData]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [CData]) -> Element Source #

Node ([Attr], [Content]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Content]) -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.Pandoc.XML.Light.Types

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

unode :: Node t => Text -> t -> Element Source #

Create node with unqualified name

add_attr :: Attr -> Element -> Element Source #

Add an attribute to an element.

add_attrs :: [Attr] -> Element -> Element Source #

Add some attributes to an element.

Conversion functions from xml-light types