Copyright | Copyright (C) 2012-2016 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Data structures and functions for representing parser and writer options.
- data Extension
- = Ext_footnotes
- | Ext_inline_notes
- | Ext_pandoc_title_block
- | Ext_yaml_metadata_block
- | Ext_mmd_title_block
- | Ext_table_captions
- | Ext_implicit_figures
- | Ext_simple_tables
- | Ext_multiline_tables
- | Ext_grid_tables
- | Ext_pipe_tables
- | Ext_citations
- | Ext_raw_tex
- | Ext_raw_html
- | Ext_tex_math_dollars
- | Ext_tex_math_single_backslash
- | Ext_tex_math_double_backslash
- | Ext_latex_macros
- | Ext_fenced_code_blocks
- | Ext_fenced_code_attributes
- | Ext_backtick_code_blocks
- | Ext_inline_code_attributes
- | Ext_markdown_in_html_blocks
- | Ext_native_divs
- | Ext_native_spans
- | Ext_bracketed_spans
- | Ext_markdown_attribute
- | Ext_escaped_line_breaks
- | Ext_link_attributes
- | Ext_mmd_link_attributes
- | Ext_autolink_bare_uris
- | Ext_fancy_lists
- | Ext_lists_without_preceding_blankline
- | Ext_startnum
- | Ext_definition_lists
- | Ext_compact_definition_lists
- | Ext_example_lists
- | Ext_all_symbols_escapable
- | Ext_angle_brackets_escapable
- | Ext_intraword_underscores
- | Ext_blank_before_blockquote
- | Ext_blank_before_header
- | Ext_strikeout
- | Ext_superscript
- | Ext_subscript
- | Ext_hard_line_breaks
- | Ext_ignore_line_breaks
- | Ext_east_asian_line_breaks
- | Ext_literate_haskell
- | Ext_abbreviations
- | Ext_emoji
- | Ext_auto_identifiers
- | Ext_ascii_identifiers
- | Ext_header_attributes
- | Ext_mmd_header_identifiers
- | Ext_implicit_header_references
- | Ext_line_blocks
- | Ext_epub_html_exts
- | Ext_shortcut_reference_links
- pandocExtensions :: Set Extension
- plainExtensions :: Set Extension
- strictExtensions :: Set Extension
- phpMarkdownExtraExtensions :: Set Extension
- githubMarkdownExtensions :: Set Extension
- multimarkdownExtensions :: Set Extension
- data ReaderOptions = ReaderOptions {
- readerExtensions :: Set Extension
- readerSmart :: Bool
- readerStandalone :: Bool
- readerParseRaw :: Bool
- readerColumns :: Int
- readerTabStop :: Int
- readerOldDashes :: Bool
- readerApplyMacros :: Bool
- readerIndentedCodeClasses :: [String]
- readerDefaultImageExtension :: String
- readerTrace :: Bool
- readerTrackChanges :: TrackChanges
- readerFileScope :: Bool
- data HTMLMathMethod
- data CiteMethod
- data ObfuscationMethod
- data HTMLSlideVariant
- data EPUBVersion
- data WrapOption
- data TopLevelDivision
- data WriterOptions = WriterOptions {
- writerTemplate :: Maybe String
- writerVariables :: [(String, String)]
- writerTabStop :: Int
- writerTableOfContents :: Bool
- writerSlideVariant :: HTMLSlideVariant
- writerIncremental :: Bool
- writerHTMLMathMethod :: HTMLMathMethod
- writerIgnoreNotes :: Bool
- writerNumberSections :: Bool
- writerNumberOffset :: [Int]
- writerSectionDivs :: Bool
- writerExtensions :: Set Extension
- writerReferenceLinks :: Bool
- writerDpi :: Int
- writerWrapText :: WrapOption
- writerColumns :: Int
- writerEmailObfuscation :: ObfuscationMethod
- writerIdentifierPrefix :: String
- writerSourceURL :: Maybe String
- writerUserDataDir :: Maybe FilePath
- writerCiteMethod :: CiteMethod
- writerDocbook5 :: Bool
- writerHtml5 :: Bool
- writerHtmlQTags :: Bool
- writerBeamer :: Bool
- writerSlideLevel :: Maybe Int
- writerTopLevelDivision :: TopLevelDivision
- writerListings :: Bool
- writerHighlight :: Bool
- writerHighlightStyle :: Style
- writerSetextHeaders :: Bool
- writerTeXLigatures :: Bool
- writerEpubVersion :: Maybe EPUBVersion
- writerEpubMetadata :: String
- writerEpubStylesheet :: Maybe String
- writerEpubFonts :: [FilePath]
- writerEpubChapterLevel :: Int
- writerTOCDepth :: Int
- writerReferenceODT :: Maybe FilePath
- writerReferenceDocx :: Maybe FilePath
- writerMediaBag :: MediaBag
- writerVerbose :: Bool
- writerLaTeXArgs :: [String]
- writerReferenceLocation :: ReferenceLocation
- data TrackChanges
- data ReferenceLocation
- def :: Default a => a
- isEnabled :: Extension -> WriterOptions -> Bool
Documentation
Individually selectable syntax extensions.
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_bracketed_spans | Bracketed spans with attributes |
Ext_markdown_attribute | Interpret text inside HTML as markdown
iff container has attribute |
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_angle_brackets_escapable | Make and 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 |
data ReaderOptions Source #
ReaderOptions | |
|
data HTMLMathMethod Source #
data CiteMethod Source #
data ObfuscationMethod Source #
Methods for obfuscating email addresses in HTML.
data HTMLSlideVariant Source #
Varieties of HTML slide shows.
data EPUBVersion Source #
data WrapOption Source #
Options for wrapping text in the output.
WrapAuto | Automatically wrap to width |
WrapNone | No non-semantic newlines |
WrapPreserve | Preserve wrapping of input source |
data TopLevelDivision Source #
Options defining the type of top-level headers.
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 |
data WriterOptions Source #
Options for writers
WriterOptions | |
|
data TrackChanges Source #
Options for accepting or rejecting MS Word track-changes.
data ReferenceLocation Source #
Locations for footnotes and references in markdown output
EndOfBlock | End of block |
EndOfSection | prior to next section header (or end of document) |
EndOfDocument | at end of document |