Copyright | Copyright (C) 2012-2020 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Data structures and functions for representing markup extensions.
Synopsis
- data Extension
- = Ext_abbreviations
- | Ext_all_symbols_escapable
- | Ext_amuse
- | Ext_angle_brackets_escapable
- | Ext_ascii_identifiers
- | Ext_auto_identifiers
- | Ext_autolink_bare_uris
- | Ext_backtick_code_blocks
- | Ext_blank_before_blockquote
- | Ext_blank_before_header
- | Ext_bracketed_spans
- | Ext_citations
- | Ext_compact_definition_lists
- | Ext_definition_lists
- | Ext_east_asian_line_breaks
- | Ext_emoji
- | Ext_empty_paragraphs
- | Ext_epub_html_exts
- | Ext_escaped_line_breaks
- | Ext_example_lists
- | Ext_fancy_lists
- | Ext_fenced_code_attributes
- | Ext_fenced_code_blocks
- | Ext_fenced_divs
- | Ext_footnotes
- | Ext_four_space_rule
- | Ext_gfm_auto_identifiers
- | Ext_grid_tables
- | Ext_hard_line_breaks
- | Ext_header_attributes
- | Ext_ignore_line_breaks
- | Ext_implicit_figures
- | Ext_implicit_header_references
- | Ext_inline_code_attributes
- | Ext_inline_notes
- | Ext_intraword_underscores
- | Ext_latex_macros
- | Ext_line_blocks
- | Ext_link_attributes
- | Ext_lists_without_preceding_blankline
- | Ext_literate_haskell
- | Ext_markdown_attribute
- | Ext_markdown_in_html_blocks
- | Ext_mmd_header_identifiers
- | Ext_mmd_link_attributes
- | Ext_mmd_title_block
- | Ext_multiline_tables
- | Ext_native_divs
- | Ext_native_spans
- | Ext_native_numbering
- | Ext_ntb
- | Ext_old_dashes
- | Ext_pandoc_title_block
- | Ext_pipe_tables
- | Ext_raw_attribute
- | Ext_raw_html
- | Ext_raw_tex
- | Ext_raw_markdown
- | Ext_shortcut_reference_links
- | Ext_simple_tables
- | Ext_smart
- | Ext_space_in_atx_header
- | Ext_spaced_reference_links
- | Ext_startnum
- | Ext_strikeout
- | Ext_subscript
- | Ext_superscript
- | Ext_styles
- | Ext_task_lists
- | Ext_table_captions
- | Ext_tex_math_dollars
- | Ext_tex_math_double_backslash
- | Ext_tex_math_single_backslash
- | Ext_yaml_metadata_block
- | Ext_gutenberg
- | Ext_attributes
- data Extensions
- emptyExtensions :: Extensions
- extensionsFromList :: [Extension] -> Extensions
- parseFormatSpec :: Text -> Either ParseError (Text, [Extension], [Extension])
- extensionEnabled :: Extension -> Extensions -> Bool
- enableExtension :: Extension -> Extensions -> Extensions
- disableExtension :: Extension -> Extensions -> Extensions
- getDefaultExtensions :: Text -> Extensions
- getAllExtensions :: Text -> Extensions
- pandocExtensions :: Extensions
- plainExtensions :: Extensions
- strictExtensions :: Extensions
- phpMarkdownExtraExtensions :: Extensions
- githubMarkdownExtensions :: Extensions
- multimarkdownExtensions :: Extensions
Documentation
Individually selectable syntax extensions.
Ext_abbreviations | PHP markdown extra abbreviation definitions |
Ext_all_symbols_escapable | Make all non-alphanumerics escapable |
Ext_amuse | Enable Text::Amuse extensions to Emacs Muse markup |
Ext_angle_brackets_escapable | Make and escapable |
Ext_ascii_identifiers | ascii-only identifiers for headers; presupposes Ext_auto_identifiers |
Ext_auto_identifiers | Automatic identifiers for headers |
Ext_autolink_bare_uris | Make all absolute URIs into links |
Ext_backtick_code_blocks | GitHub style ``` code blocks |
Ext_blank_before_blockquote | Require blank line before a blockquote |
Ext_blank_before_header | Require blank line before a header |
Ext_bracketed_spans | Bracketed spans with attributes |
Ext_citations | Pandoc/citeproc citations |
Ext_compact_definition_lists | Definition lists without space between items, and disallow laziness |
Ext_definition_lists | Definition lists as in pandoc, mmd, php |
Ext_east_asian_line_breaks | Newlines in paragraphs are ignored between East Asian wide characters. Note: this extension does not affect readers/writers directly; it causes the eastAsianLineBreakFilter to be applied after parsing, in Text.Pandoc.App.convertWithOpts. |
Ext_emoji | Support emoji like :smile: |
Ext_empty_paragraphs | Allow empty paragraphs |
Ext_epub_html_exts | Recognise the EPUB extended version of HTML |
Ext_escaped_line_breaks | Treat a backslash at EOL as linebreak |
Ext_example_lists | Markdown-style numbered examples |
Ext_fancy_lists | Enable fancy list numbers and delimiters |
Ext_fenced_code_attributes | Allow attributes on fenced code blocks |
Ext_fenced_code_blocks | Parse fenced code blocks |
Ext_fenced_divs | Allow fenced div syntax ::: |
Ext_footnotes | Pandoc/PHP/MMD style footnotes |
Ext_four_space_rule | Require 4-space indent for list contents |
Ext_gfm_auto_identifiers | Use GitHub's method for generating header identifiers; presupposes Ext_auto_identifiers |
Ext_grid_tables | Grid tables (pandoc, reST) |
Ext_hard_line_breaks | All newlines become hard line breaks |
Ext_header_attributes | Explicit header attributes {#id .class k=v} |
Ext_ignore_line_breaks | Newlines in paragraphs are ignored |
Ext_implicit_figures | A paragraph with just an image is a figure |
Ext_implicit_header_references | Implicit reference links for headers |
Ext_inline_code_attributes | Allow attributes on inline code |
Ext_inline_notes | Pandoc-style inline notes |
Ext_intraword_underscores | Treat underscore inside word as literal |
Ext_latex_macros | Parse LaTeX macro definitions (for math only) |
Ext_line_blocks | RST style line blocks |
Ext_link_attributes | link and image attributes |
Ext_lists_without_preceding_blankline | Allow lists without preceding blank |
Ext_literate_haskell | Enable literate Haskell conventions |
Ext_markdown_attribute | Interpret text inside HTML as markdown iff
container has attribute |
Ext_markdown_in_html_blocks | Interpret as markdown inside HTML blocks |
Ext_mmd_header_identifiers | Multimarkdown style header identifiers [myid] |
Ext_mmd_link_attributes | MMD style reference link attributes |
Ext_mmd_title_block | Multimarkdown metadata block |
Ext_multiline_tables | Pandoc-style multiline tables |
Ext_native_divs | Use Div blocks for contents of div tags |
Ext_native_spans | Use Span inlines for contents of span |
Ext_native_numbering | Use output format's native numbering for figures and tables |
Ext_ntb | ConTeXt Natural Tables |
Ext_old_dashes |
|
Ext_pandoc_title_block | Pandoc title block |
Ext_pipe_tables | Pipe tables (as in PHP markdown extra) |
Ext_raw_attribute | Allow explicit raw blocks/inlines |
Ext_raw_html | Allow raw HTML |
Ext_raw_tex | Allow raw TeX (other than math) |
Ext_raw_markdown | Parse markdown in ipynb as raw markdown |
Ext_shortcut_reference_links | Shortcut reference links |
Ext_simple_tables | Pandoc-style simple tables |
Ext_smart | Smart quotes, apostrophes, ellipses, dashes |
Ext_space_in_atx_header | Require space between # and header text |
Ext_spaced_reference_links | Allow space between two parts of ref link |
Ext_startnum | Make start number of ordered list significant |
Ext_strikeout | Strikeout using ~~this~~ syntax |
Ext_subscript | Subscript using ~this~ syntax |
Ext_superscript | Superscript using ^this^ syntax |
Ext_styles | Read styles that pandoc doesn't know |
Ext_task_lists | Parse certain list items as task list items |
Ext_table_captions | Pandoc-style table captions |
Ext_tex_math_dollars | TeX math between $..$ or $$..$$ |
Ext_tex_math_double_backslash | TeX math btw \(..\) \[..\] |
Ext_tex_math_single_backslash | TeX math btw \(..\) \[..\] |
Ext_yaml_metadata_block | YAML metadata block |
Ext_gutenberg | Use Project Gutenberg conventions for plain |
Ext_attributes | Generic attribute syntax |
Instances
Bounded Extension Source # | |
Enum Extension Source # | |
Defined in Text.Pandoc.Extensions succ :: Extension -> Extension # pred :: Extension -> Extension # fromEnum :: Extension -> Int # enumFrom :: Extension -> [Extension] # enumFromThen :: Extension -> Extension -> [Extension] # enumFromTo :: Extension -> Extension -> [Extension] # enumFromThenTo :: Extension -> Extension -> Extension -> [Extension] # | |
Eq Extension Source # | |
Data Extension Source # | |
Defined in Text.Pandoc.Extensions 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 # | |
Defined in Text.Pandoc.Extensions | |
Read Extension Source # | |
Show Extension Source # | |
Generic Extension Source # | |
ToJSON Extension Source # | |
Defined in Text.Pandoc.Extensions | |
FromJSON Extension Source # | |
type Rep Extension Source # | |
Defined in Text.Pandoc.Extensions type Rep Extension = D1 (MetaData "Extension" "Text.Pandoc.Extensions" "pandoc-2.11.0.3-2cmwCSqRRKHAD5FoQD2nQc" False) ((((((C1 (MetaCons "Ext_abbreviations" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_all_symbols_escapable" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_amuse" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_angle_brackets_escapable" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Ext_ascii_identifiers" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_auto_identifiers" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_autolink_bare_uris" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_backtick_code_blocks" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_blank_before_blockquote" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Ext_blank_before_header" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_bracketed_spans" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_citations" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_compact_definition_lists" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_definition_lists" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Ext_east_asian_line_breaks" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_emoji" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_empty_paragraphs" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_epub_html_exts" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_escaped_line_breaks" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "Ext_example_lists" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_fancy_lists" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_fenced_code_attributes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_fenced_code_blocks" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Ext_fenced_divs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_footnotes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_four_space_rule" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_gfm_auto_identifiers" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_grid_tables" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Ext_hard_line_breaks" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_header_attributes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_ignore_line_breaks" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_implicit_figures" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_implicit_header_references" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Ext_inline_code_attributes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_inline_notes" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_intraword_underscores" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_latex_macros" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_line_blocks" PrefixI False) (U1 :: Type -> Type))))))) :+: (((((C1 (MetaCons "Ext_link_attributes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_lists_without_preceding_blankline" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_literate_haskell" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_markdown_attribute" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Ext_markdown_in_html_blocks" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_mmd_header_identifiers" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_mmd_link_attributes" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_mmd_title_block" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_multiline_tables" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Ext_native_divs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_native_spans" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_native_numbering" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_ntb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_old_dashes" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Ext_pandoc_title_block" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_pipe_tables" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_raw_attribute" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_raw_html" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_raw_tex" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "Ext_raw_markdown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_shortcut_reference_links" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_simple_tables" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_smart" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Ext_space_in_atx_header" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_spaced_reference_links" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_startnum" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_strikeout" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_subscript" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Ext_superscript" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_styles" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_task_lists" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_table_captions" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_tex_math_dollars" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Ext_tex_math_double_backslash" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_tex_math_single_backslash" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ext_yaml_metadata_block" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ext_gutenberg" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ext_attributes" PrefixI False) (U1 :: Type -> Type)))))))) |
data Extensions Source #
Instances
extensionsFromList :: [Extension] -> Extensions Source #
parseFormatSpec :: Text -> Either ParseError (Text, [Extension], [Extension]) Source #
Parse a format-specifying string into a markup format, a set of extensions to enable, and a set of extensions to disable.
extensionEnabled :: Extension -> Extensions -> Bool Source #
enableExtension :: Extension -> Extensions -> Extensions Source #
disableExtension :: Extension -> Extensions -> Extensions Source #
getDefaultExtensions :: Text -> Extensions Source #
Default extensions from format-describing string.
getAllExtensions :: Text -> Extensions Source #
Get all valid extensions for a format. This is used mainly in checking format specifications for validity.
pandocExtensions :: Extensions Source #
Extensions to be used with pandoc-flavored markdown.
plainExtensions :: Extensions Source #
Extensions to be used with plain text output.
strictExtensions :: Extensions Source #
Language extensions to be used with strict markdown.
phpMarkdownExtraExtensions :: Extensions Source #
Extensions to be used with PHP Markdown Extra.
githubMarkdownExtensions :: Extensions Source #
Extensions to be used with github-flavored markdown.
multimarkdownExtensions :: Extensions Source #
Extensions to be used with multimarkdown.