pandoc-2.0.4: Conversion between markup formats

CopyrightCopyright (C) 2012-2017 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.Pandoc.Options

Description

Data structures and functions for representing parser and writer options.

Synopsis

Documentation

data ReaderOptions Source #

Constructors

ReaderOptions 

Fields

Instances

Data ReaderOptions Source # 

Methods

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

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

toConstr :: ReaderOptions -> Constr #

dataTypeOf :: ReaderOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReaderOptions Source # 
Show ReaderOptions Source # 
Generic ReaderOptions Source # 

Associated Types

type Rep ReaderOptions :: * -> * #

FromJSON ReaderOptions Source # 
ToJSON ReaderOptions Source # 
Default ReaderOptions Source # 

Methods

def :: ReaderOptions #

type Rep ReaderOptions Source # 

data HTMLMathMethod Source #

Instances

Eq HTMLMathMethod Source # 
Data HTMLMathMethod Source # 

Methods

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

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

toConstr :: HTMLMathMethod -> Constr #

dataTypeOf :: HTMLMathMethod -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HTMLMathMethod Source # 
Show HTMLMathMethod Source # 
Generic HTMLMathMethod Source # 

Associated Types

type Rep HTMLMathMethod :: * -> * #

FromJSON HTMLMathMethod Source # 
ToJSON HTMLMathMethod Source # 
type Rep HTMLMathMethod Source # 

data CiteMethod Source #

Constructors

Citeproc 
Natbib 
Biblatex 

Instances

Eq CiteMethod Source # 
Data CiteMethod Source # 

Methods

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

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

toConstr :: CiteMethod -> Constr #

dataTypeOf :: CiteMethod -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CiteMethod Source # 
Show CiteMethod Source # 
Generic CiteMethod Source # 

Associated Types

type Rep CiteMethod :: * -> * #

FromJSON CiteMethod Source # 
ToJSON CiteMethod Source # 
type Rep CiteMethod Source # 
type Rep CiteMethod = D1 (MetaData "CiteMethod" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "Citeproc" PrefixI False) U1) ((:+:) (C1 (MetaCons "Natbib" PrefixI False) U1) (C1 (MetaCons "Biblatex" PrefixI False) U1)))

data ObfuscationMethod Source #

Methods for obfuscating email addresses in HTML.

Instances

Eq ObfuscationMethod Source # 
Data ObfuscationMethod Source # 

Methods

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

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

toConstr :: ObfuscationMethod -> Constr #

dataTypeOf :: ObfuscationMethod -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ObfuscationMethod Source # 
Show ObfuscationMethod Source # 
Generic ObfuscationMethod Source # 
FromJSON ObfuscationMethod Source # 
ToJSON ObfuscationMethod Source # 
type Rep ObfuscationMethod Source # 
type Rep ObfuscationMethod = D1 (MetaData "ObfuscationMethod" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "NoObfuscation" PrefixI False) U1) ((:+:) (C1 (MetaCons "ReferenceObfuscation" PrefixI False) U1) (C1 (MetaCons "JavascriptObfuscation" PrefixI False) U1)))

data HTMLSlideVariant Source #

Varieties of HTML slide shows.

Instances

Eq HTMLSlideVariant Source # 
Data HTMLSlideVariant Source # 

Methods

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

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

toConstr :: HTMLSlideVariant -> Constr #

dataTypeOf :: HTMLSlideVariant -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HTMLSlideVariant Source # 
Show HTMLSlideVariant Source # 
Generic HTMLSlideVariant Source # 
FromJSON HTMLSlideVariant Source # 
ToJSON HTMLSlideVariant Source # 
type Rep HTMLSlideVariant Source # 
type Rep HTMLSlideVariant = D1 (MetaData "HTMLSlideVariant" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) ((:+:) (C1 (MetaCons "S5Slides" PrefixI False) U1) ((:+:) (C1 (MetaCons "SlidySlides" PrefixI False) U1) (C1 (MetaCons "SlideousSlides" PrefixI False) U1))) ((:+:) (C1 (MetaCons "DZSlides" PrefixI False) U1) ((:+:) (C1 (MetaCons "RevealJsSlides" PrefixI False) U1) (C1 (MetaCons "NoSlides" PrefixI False) U1))))

data EPUBVersion Source #

Constructors

EPUB2 
EPUB3 

Instances

Eq EPUBVersion Source # 
Data EPUBVersion Source # 

Methods

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

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

toConstr :: EPUBVersion -> Constr #

dataTypeOf :: EPUBVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EPUBVersion Source # 
Show EPUBVersion Source # 
Generic EPUBVersion Source # 

Associated Types

type Rep EPUBVersion :: * -> * #

type Rep EPUBVersion Source # 
type Rep EPUBVersion = D1 (MetaData "EPUBVersion" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "EPUB2" PrefixI False) U1) (C1 (MetaCons "EPUB3" PrefixI False) U1))

data WrapOption Source #

Options for wrapping text in the output.

Constructors

WrapAuto

Automatically wrap to width

WrapNone

No non-semantic newlines

WrapPreserve

Preserve wrapping of input source

Instances

Eq WrapOption Source # 
Data WrapOption Source # 

Methods

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

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

toConstr :: WrapOption -> Constr #

dataTypeOf :: WrapOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WrapOption Source # 
Show WrapOption Source # 
Generic WrapOption Source # 

Associated Types

type Rep WrapOption :: * -> * #

FromJSON WrapOption Source # 
ToJSON WrapOption Source # 
type Rep WrapOption Source # 
type Rep WrapOption = D1 (MetaData "WrapOption" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "WrapAuto" PrefixI False) U1) ((:+:) (C1 (MetaCons "WrapNone" PrefixI False) U1) (C1 (MetaCons "WrapPreserve" PrefixI False) U1)))

data TopLevelDivision Source #

Options defining the type of top-level headers.

Constructors

TopLevelPart

Top-level headers become parts

TopLevelChapter

Top-level headers become chapters

TopLevelSection

Top-level headers become sections

TopLevelDefault

Top-level type is determined via heuristics

Instances

Eq TopLevelDivision Source # 
Data TopLevelDivision Source # 

Methods

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

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

toConstr :: TopLevelDivision -> Constr #

dataTypeOf :: TopLevelDivision -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TopLevelDivision Source # 
Show TopLevelDivision Source # 
Generic TopLevelDivision Source # 
FromJSON TopLevelDivision Source # 
ToJSON TopLevelDivision Source # 
type Rep TopLevelDivision Source # 
type Rep TopLevelDivision = D1 (MetaData "TopLevelDivision" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) ((:+:) (C1 (MetaCons "TopLevelPart" PrefixI False) U1) (C1 (MetaCons "TopLevelChapter" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TopLevelSection" PrefixI False) U1) (C1 (MetaCons "TopLevelDefault" PrefixI False) U1)))

data WriterOptions Source #

Options for writers

Constructors

WriterOptions 

Fields

Instances

Data WriterOptions Source # 

Methods

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

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

toConstr :: WriterOptions -> Constr #

dataTypeOf :: WriterOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Show WriterOptions Source # 
Generic WriterOptions Source # 

Associated Types

type Rep WriterOptions :: * -> * #

Default WriterOptions Source # 

Methods

def :: WriterOptions #

type Rep WriterOptions Source # 
type Rep WriterOptions = D1 (MetaData "WriterOptions" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) (C1 (MetaCons "WriterOptions" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerTemplate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) ((:*:) (S1 (MetaSel (Just Symbol "writerVariables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)])) (S1 (MetaSel (Just Symbol "writerTabStop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerTableOfContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerIncremental") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "writerHTMLMathMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HTMLMathMethod)) (S1 (MetaSel (Just Symbol "writerNumberSections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerNumberOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])) (S1 (MetaSel (Just Symbol "writerSectionDivs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "writerExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Extensions)) (S1 (MetaSel (Just Symbol "writerReferenceLinks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerDpi") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "writerWrapText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WrapOption))) ((:*:) (S1 (MetaSel (Just Symbol "writerColumns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "writerEmailObfuscation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObfuscationMethod)))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerIdentifierPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "writerCiteMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CiteMethod))) ((:*:) (S1 (MetaSel (Just Symbol "writerHtmlQTags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerSlideLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerTopLevelDivision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TopLevelDivision)) (S1 (MetaSel (Just Symbol "writerListings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "writerHighlightStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Style))) (S1 (MetaSel (Just Symbol "writerSetextHeaders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerEpubSubdirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "writerEpubMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "writerEpubFonts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) (S1 (MetaSel (Just Symbol "writerEpubChapterLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerTOCDepth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "writerReferenceDoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath)))) ((:*:) (S1 (MetaSel (Just Symbol "writerReferenceLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReferenceLocation)) (S1 (MetaSel (Just Symbol "writerSyntaxMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SyntaxMap))))))))

data TrackChanges Source #

Options for accepting or rejecting MS Word track-changes.

Instances

Eq TrackChanges Source # 
Data TrackChanges Source # 

Methods

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

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

toConstr :: TrackChanges -> Constr #

dataTypeOf :: TrackChanges -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TrackChanges Source # 
Show TrackChanges Source # 
Generic TrackChanges Source # 

Associated Types

type Rep TrackChanges :: * -> * #

FromJSON TrackChanges Source # 
ToJSON TrackChanges Source # 
type Rep TrackChanges Source # 
type Rep TrackChanges = D1 (MetaData "TrackChanges" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "AcceptChanges" PrefixI False) U1) ((:+:) (C1 (MetaCons "RejectChanges" PrefixI False) U1) (C1 (MetaCons "AllChanges" PrefixI False) U1)))

data ReferenceLocation Source #

Locations for footnotes and references in markdown output

Constructors

EndOfBlock

End of block

EndOfSection

prior to next section header (or end of document)

EndOfDocument

at end of document

Instances

Eq ReferenceLocation Source # 
Data ReferenceLocation Source # 

Methods

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

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

toConstr :: ReferenceLocation -> Constr #

dataTypeOf :: ReferenceLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReferenceLocation Source # 
Show ReferenceLocation Source # 
Generic ReferenceLocation Source # 
FromJSON ReferenceLocation Source # 
ToJSON ReferenceLocation Source # 
type Rep ReferenceLocation Source # 
type Rep ReferenceLocation = D1 (MetaData "ReferenceLocation" "Text.Pandoc.Options" "pandoc-2.0.4-3lKSvonRkGzITuXJfQHK9c" False) ((:+:) (C1 (MetaCons "EndOfBlock" PrefixI False) U1) ((:+:) (C1 (MetaCons "EndOfSection" PrefixI False) U1) (C1 (MetaCons "EndOfDocument" PrefixI False) U1)))

def :: Default a => a #

The default value for this type.

isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool Source #

Returns True if the given extension is enabled.