pandoc-1.17.2: Conversion between markup formats

CopyrightCopyright (C) 2012-2016 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 Extension Source #

Individually selectable syntax extensions.

Constructors

Ext_footnotes

PandocPHPMMD style footnotes

Ext_inline_notes

Pandoc-style inline notes

Ext_pandoc_title_block

Pandoc title block

Ext_yaml_metadata_block

YAML metadata block

Ext_mmd_title_block

Multimarkdown metadata block

Ext_table_captions

Pandoc-style table captions

Ext_implicit_figures

A paragraph with just an image is a figure

Ext_simple_tables

Pandoc-style simple tables

Ext_multiline_tables

Pandoc-style multiline tables

Ext_grid_tables

Grid tables (pandoc, reST)

Ext_pipe_tables

Pipe tables (as in PHP markdown extra)

Ext_citations

Pandoc/citeproc citations

Ext_raw_tex

Allow raw TeX (other than math)

Ext_raw_html

Allow raw HTML

Ext_tex_math_dollars

TeX math between $..$ or $$..$$

Ext_tex_math_single_backslash

TeX math btw \(..\) \[..\]

Ext_tex_math_double_backslash

TeX math btw \(..\) \[..\]

Ext_latex_macros

Parse LaTeX macro definitions (for math only)

Ext_fenced_code_blocks

Parse fenced code blocks

Ext_fenced_code_attributes

Allow attributes on fenced code blocks

Ext_backtick_code_blocks

GitHub style ``` code blocks

Ext_inline_code_attributes

Allow attributes on inline code

Ext_markdown_in_html_blocks

Interpret as markdown inside HTML blocks

Ext_native_divs

Use Div blocks for contents of div tags

Ext_native_spans

Use Span inlines for contents of span

Ext_markdown_attribute

Interpret text inside HTML as markdown iff container has attribute markdown

Ext_escaped_line_breaks

Treat a backslash at EOL as linebreak

Ext_link_attributes

link and image attributes

Ext_mmd_link_attributes

MMD style reference link attributes

Ext_autolink_bare_uris

Make all absolute URIs into links

Ext_fancy_lists

Enable fancy list numbers and delimiters

Ext_lists_without_preceding_blankline

Allow lists without preceding blank

Ext_startnum

Make start number of ordered list significant

Ext_definition_lists

Definition lists as in pandoc, mmd, php

Ext_compact_definition_lists

Definition lists without space between items, and disallow laziness

Ext_example_lists

Markdown-style numbered examples

Ext_all_symbols_escapable

Make all non-alphanumerics escapable

Ext_intraword_underscores

Treat underscore inside word as literal

Ext_blank_before_blockquote

Require blank line before a blockquote

Ext_blank_before_header

Require blank line before a header

Ext_strikeout

Strikeout using ~~this~~ syntax

Ext_superscript

Superscript using ^this^ syntax

Ext_subscript

Subscript using ~this~ syntax

Ext_hard_line_breaks

All newlines become hard line breaks

Ext_ignore_line_breaks

Newlines in paragraphs are ignored

Ext_east_asian_line_breaks

Newlines in paragraphs are ignored between East Asian wide characters

Ext_literate_haskell

Enable literate Haskell conventions

Ext_abbreviations

PHP markdown extra abbreviation definitions

Ext_emoji

Support emoji like :smile:

Ext_auto_identifiers

Automatic identifiers for headers

Ext_ascii_identifiers

ascii-only identifiers for headers

Ext_header_attributes

Explicit header attributes {#id .class k=v}

Ext_mmd_header_identifiers

Multimarkdown style header identifiers [myid]

Ext_implicit_header_references

Implicit reference links for headers

Ext_line_blocks

RST style line blocks

Ext_epub_html_exts

Recognise the EPUB extended version of HTML

Ext_shortcut_reference_links

Shortcut reference links

Instances

Bounded Extension Source # 
Enum Extension Source # 
Eq Extension Source # 
Data Extension Source # 

Methods

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

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

toConstr :: Extension -> Constr #

dataTypeOf :: Extension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Extension Source # 
Read Extension Source # 
Show Extension Source # 
Generic Extension Source # 

Associated Types

type Rep Extension :: * -> * #

type Rep Extension Source # 
type Rep Extension = D1 (MetaData "Extension" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ext_footnotes" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_inline_notes" PrefixI False) U1) (C1 (MetaCons "Ext_pandoc_title_block" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_yaml_metadata_block" PrefixI False) U1) (C1 (MetaCons "Ext_mmd_title_block" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_table_captions" PrefixI False) U1) (C1 (MetaCons "Ext_implicit_figures" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Ext_simple_tables" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_multiline_tables" PrefixI False) U1) (C1 (MetaCons "Ext_grid_tables" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_pipe_tables" PrefixI False) U1) (C1 (MetaCons "Ext_citations" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_raw_tex" PrefixI False) U1) (C1 (MetaCons "Ext_raw_html" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ext_tex_math_dollars" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_tex_math_single_backslash" PrefixI False) U1) (C1 (MetaCons "Ext_tex_math_double_backslash" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_latex_macros" PrefixI False) U1) (C1 (MetaCons "Ext_fenced_code_blocks" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_fenced_code_attributes" PrefixI False) U1) (C1 (MetaCons "Ext_backtick_code_blocks" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Ext_inline_code_attributes" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_markdown_in_html_blocks" PrefixI False) U1) (C1 (MetaCons "Ext_native_divs" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_native_spans" PrefixI False) U1) (C1 (MetaCons "Ext_markdown_attribute" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_escaped_line_breaks" PrefixI False) U1) (C1 (MetaCons "Ext_link_attributes" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ext_mmd_link_attributes" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_autolink_bare_uris" PrefixI False) U1) (C1 (MetaCons "Ext_fancy_lists" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_lists_without_preceding_blankline" PrefixI False) U1) (C1 (MetaCons "Ext_startnum" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_definition_lists" PrefixI False) U1) (C1 (MetaCons "Ext_compact_definition_lists" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Ext_example_lists" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_all_symbols_escapable" PrefixI False) U1) (C1 (MetaCons "Ext_intraword_underscores" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_blank_before_blockquote" PrefixI False) U1) (C1 (MetaCons "Ext_blank_before_header" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_strikeout" PrefixI False) U1) (C1 (MetaCons "Ext_superscript" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ext_subscript" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ext_hard_line_breaks" PrefixI False) U1) (C1 (MetaCons "Ext_ignore_line_breaks" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_east_asian_line_breaks" PrefixI False) U1) (C1 (MetaCons "Ext_literate_haskell" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_abbreviations" PrefixI False) U1) (C1 (MetaCons "Ext_emoji" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ext_auto_identifiers" PrefixI False) U1) (C1 (MetaCons "Ext_ascii_identifiers" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_header_attributes" PrefixI False) U1) (C1 (MetaCons "Ext_mmd_header_identifiers" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Ext_implicit_header_references" PrefixI False) U1) (C1 (MetaCons "Ext_line_blocks" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Ext_epub_html_exts" PrefixI False) U1) (C1 (MetaCons "Ext_shortcut_reference_links" PrefixI False) U1)))))))

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 :: * -> * #

Default ReaderOptions Source # 

Methods

def :: ReaderOptions #

type Rep ReaderOptions Source # 
type Rep ReaderOptions = D1 (MetaData "ReaderOptions" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" False) (C1 (MetaCons "ReaderOptions" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "readerExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Extension))) ((:*:) (S1 (MetaSel (Just Symbol "readerSmart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "readerStandalone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "readerParseRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "readerColumns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "readerTabStop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "readerOldDashes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "readerApplyMacros") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "readerIndentedCodeClasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "readerDefaultImageExtension") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "readerTrace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "readerTrackChanges") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TrackChanges)) (S1 (MetaSel (Just Symbol "readerFileScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))))

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 :: * -> * #

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 :: * -> * #

type Rep CiteMethod Source # 
type Rep CiteMethod = D1 (MetaData "CiteMethod" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" 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 # 
type Rep ObfuscationMethod Source # 
type Rep ObfuscationMethod = D1 (MetaData "ObfuscationMethod" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" 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 # 
type Rep HTMLSlideVariant Source # 
type Rep HTMLSlideVariant = D1 (MetaData "HTMLSlideVariant" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" 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-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" 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 :: * -> * #

type Rep WrapOption Source # 
type Rep WrapOption = D1 (MetaData "WrapOption" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" False) ((:+:) (C1 (MetaCons "WrapAuto" PrefixI False) U1) ((:+:) (C1 (MetaCons "WrapNone" PrefixI False) U1) (C1 (MetaCons "WrapPreserve" 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-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" False) (C1 (MetaCons "WriterOptions" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerStandalone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerTemplate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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 "writerSlideVariant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HTMLSlideVariant)) ((:*:) (S1 (MetaSel (Just Symbol "writerIncremental") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerHTMLMathMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HTMLMathMethod)))) ((:*:) (S1 (MetaSel (Just Symbol "writerIgnoreNotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (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 (Set Extension)))) ((:*:) (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 "writerSourceURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) ((:*:) (S1 (MetaSel (Just Symbol "writerUserDataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) (S1 (MetaSel (Just Symbol "writerCiteMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CiteMethod))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerDocbook5") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerHtml5") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "writerHtmlQTags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "writerBeamer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerSlideLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerChapters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "writerListings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerHighlight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "writerHighlightStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Style)) ((:*:) (S1 (MetaSel (Just Symbol "writerSetextHeaders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerTeXLigatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "writerEpubVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EPUBVersion))) (S1 (MetaSel (Just Symbol "writerEpubMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "writerEpubStylesheet") 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 "writerReferenceODT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) (S1 (MetaSel (Just Symbol "writerReferenceDocx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))))) ((:*:) (S1 (MetaSel (Just Symbol "writerMediaBag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MediaBag)) ((:*:) (S1 (MetaSel (Just Symbol "writerVerbose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "writerLaTeXArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))))))))

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 :: * -> * #

type Rep TrackChanges Source # 
type Rep TrackChanges = D1 (MetaData "TrackChanges" "Text.Pandoc.Options" "pandoc-1.17.2-5Yh0b7eWv6p9wNFo24hfoo" False) ((:+:) (C1 (MetaCons "AcceptChanges" PrefixI False) U1) ((:+:) (C1 (MetaCons "RejectChanges" PrefixI False) U1) (C1 (MetaCons "AllChanges" PrefixI False) U1)))

def :: Default a => a #

The default value for this type.

isEnabled :: Extension -> WriterOptions -> Bool Source #

Returns True if the given extension is enabled.