{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE OverloadedStrings          #-}
{- |
   Module      : Text.Pandoc.Extensions
   Copyright   : Copyright (C) 2012-2023 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Data structures and functions for representing markup extensions.
-}
module Text.Pandoc.Extensions ( Extension(..)
                              , readExtension
                              , showExtension
                              , Extensions
                              , emptyExtensions
                              , extensionsFromList
                              , extensionsToList
                              , extensionEnabled
                              , enableExtension
                              , disableExtension
                              , disableExtensions
                              , getDefaultExtensions
                              , getAllExtensions
                              , pandocExtensions
                              , plainExtensions
                              , strictExtensions
                              , phpMarkdownExtraExtensions
                              , githubMarkdownExtensions
                              , multimarkdownExtensions )
where
import Data.Data (Data)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Read (readMaybe)
import Data.Aeson
import Data.List (sort)
import qualified Data.Set as Set

-- | Individually selectable syntax extensions.
data Extension =
      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_attributes          -- ^ Generic attribute syntax
    | 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_element_citations   -- ^ Use element-citation elements for JATS citations
    | 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_gutenberg           -- ^ Use Project Gutenberg conventions for plain
    | 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_mark                -- ^ Enable ==mark== syntax to highlight text
    | Ext_markdown_attribute      -- ^ Interpret text inside HTML as markdown iff
                                  --   container has attribute 'markdown'
    | 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          -- ^ -- = em, - before number = en
    | 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_rebase_relative_paths -- ^ Rebase relative image and link paths,
                                -- relative to directory of containing file
    | Ext_short_subsuperscripts -- ^ sub-&superscripts w/o closing char (v~i)
    | Ext_shortcut_reference_links -- ^ Shortcut reference links
    | Ext_simple_tables       -- ^ Pandoc-style simple tables
    | Ext_smart               -- ^ "Smart" quotes, apostrophes, ellipses, dashes
    | Ext_sourcepos           -- ^ Include source position attributes
    | 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_tagging             -- ^ Output optimized for PDF tagging
    | 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_wikilinks_title_after_pipe -- ^ Support wikilinks of style
                                     -- [[target|title]]
    | Ext_wikilinks_title_before_pipe  -- ^ Support wikilinks of style
                                       -- [[title|target]]
    | Ext_xrefs_name          -- ^ Use xrefs with names
    | Ext_xrefs_number        -- ^ Use xrefs with numbers
    | Ext_yaml_metadata_block -- ^ YAML metadata block
    | CustomExtension T.Text  -- ^ Custom extension
    deriving (Int -> Extension -> ShowS
[Extension] -> ShowS
Extension -> String
(Int -> Extension -> ShowS)
-> (Extension -> String)
-> ([Extension] -> ShowS)
-> Show Extension
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Extension -> ShowS
showsPrec :: Int -> Extension -> ShowS
$cshow :: Extension -> String
show :: Extension -> String
$cshowList :: [Extension] -> ShowS
showList :: [Extension] -> ShowS
Show, ReadPrec [Extension]
ReadPrec Extension
Int -> ReadS Extension
ReadS [Extension]
(Int -> ReadS Extension)
-> ReadS [Extension]
-> ReadPrec Extension
-> ReadPrec [Extension]
-> Read Extension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Extension
readsPrec :: Int -> ReadS Extension
$creadList :: ReadS [Extension]
readList :: ReadS [Extension]
$creadPrec :: ReadPrec Extension
readPrec :: ReadPrec Extension
$creadListPrec :: ReadPrec [Extension]
readListPrec :: ReadPrec [Extension]
Read, Extension -> Extension -> Bool
(Extension -> Extension -> Bool)
-> (Extension -> Extension -> Bool) -> Eq Extension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Extension -> Extension -> Bool
== :: Extension -> Extension -> Bool
$c/= :: Extension -> Extension -> Bool
/= :: Extension -> Extension -> Bool
Eq, Eq Extension
Eq Extension
-> (Extension -> Extension -> Ordering)
-> (Extension -> Extension -> Bool)
-> (Extension -> Extension -> Bool)
-> (Extension -> Extension -> Bool)
-> (Extension -> Extension -> Bool)
-> (Extension -> Extension -> Extension)
-> (Extension -> Extension -> Extension)
-> Ord Extension
Extension -> Extension -> Bool
Extension -> Extension -> Ordering
Extension -> Extension -> Extension
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Extension -> Extension -> Ordering
compare :: Extension -> Extension -> Ordering
$c< :: Extension -> Extension -> Bool
< :: Extension -> Extension -> Bool
$c<= :: Extension -> Extension -> Bool
<= :: Extension -> Extension -> Bool
$c> :: Extension -> Extension -> Bool
> :: Extension -> Extension -> Bool
$c>= :: Extension -> Extension -> Bool
>= :: Extension -> Extension -> Bool
$cmax :: Extension -> Extension -> Extension
max :: Extension -> Extension -> Extension
$cmin :: Extension -> Extension -> Extension
min :: Extension -> Extension -> Extension
Ord, Typeable Extension
Typeable Extension
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Extension -> c Extension)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Extension)
-> (Extension -> Constr)
-> (Extension -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Extension))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension))
-> ((forall b. Data b => b -> b) -> Extension -> Extension)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Extension -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Extension -> r)
-> (forall u. (forall d. Data d => d -> u) -> Extension -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Extension -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Extension -> m Extension)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Extension -> m Extension)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Extension -> m Extension)
-> Data Extension
Extension -> Constr
Extension -> DataType
(forall b. Data b => b -> b) -> Extension -> Extension
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Extension -> u
forall u. (forall d. Data d => d -> u) -> Extension -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extension
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extension -> c Extension
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extension)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extension -> c Extension
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extension -> c Extension
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extension
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extension
$ctoConstr :: Extension -> Constr
toConstr :: Extension -> Constr
$cdataTypeOf :: Extension -> DataType
dataTypeOf :: Extension -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extension)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extension)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension)
$cgmapT :: (forall b. Data b => b -> b) -> Extension -> Extension
gmapT :: (forall b. Data b => b -> b) -> Extension -> Extension
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extension -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Extension -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Extension -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Extension -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Extension -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extension -> m Extension
Data, Typeable, (forall x. Extension -> Rep Extension x)
-> (forall x. Rep Extension x -> Extension) -> Generic Extension
forall x. Rep Extension x -> Extension
forall x. Extension -> Rep Extension x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Extension -> Rep Extension x
from :: forall x. Extension -> Rep Extension x
$cto :: forall x. Rep Extension x -> Extension
to :: forall x. Rep Extension x -> Extension
Generic)

instance FromJSON Extension where
  parseJSON :: Value -> Parser Extension
parseJSON = String -> (Text -> Parser Extension) -> Value -> Parser Extension
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Extension" (Extension -> Parser Extension
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Extension -> Parser Extension)
-> (Text -> Extension) -> Text -> Parser Extension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Extension
readExtension (String -> Extension) -> (Text -> String) -> Text -> Extension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)

instance ToJSON Extension where
 toJSON :: Extension -> Value
toJSON = Text -> Value
String (Text -> Value) -> (Extension -> Text) -> Extension -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> Text
showExtension

newtype Extensions = Extensions (Set.Set Extension)
  deriving (Int -> Extensions -> ShowS
[Extensions] -> ShowS
Extensions -> String
(Int -> Extensions -> ShowS)
-> (Extensions -> String)
-> ([Extensions] -> ShowS)
-> Show Extensions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Extensions -> ShowS
showsPrec :: Int -> Extensions -> ShowS
$cshow :: Extensions -> String
show :: Extensions -> String
$cshowList :: [Extensions] -> ShowS
showList :: [Extensions] -> ShowS
Show, ReadPrec [Extensions]
ReadPrec Extensions
Int -> ReadS Extensions
ReadS [Extensions]
(Int -> ReadS Extensions)
-> ReadS [Extensions]
-> ReadPrec Extensions
-> ReadPrec [Extensions]
-> Read Extensions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Extensions
readsPrec :: Int -> ReadS Extensions
$creadList :: ReadS [Extensions]
readList :: ReadS [Extensions]
$creadPrec :: ReadPrec Extensions
readPrec :: ReadPrec Extensions
$creadListPrec :: ReadPrec [Extensions]
readListPrec :: ReadPrec [Extensions]
Read, Extensions -> Extensions -> Bool
(Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Bool) -> Eq Extensions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Extensions -> Extensions -> Bool
== :: Extensions -> Extensions -> Bool
$c/= :: Extensions -> Extensions -> Bool
/= :: Extensions -> Extensions -> Bool
Eq, Eq Extensions
Eq Extensions
-> (Extensions -> Extensions -> Ordering)
-> (Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Extensions)
-> (Extensions -> Extensions -> Extensions)
-> Ord Extensions
Extensions -> Extensions -> Bool
Extensions -> Extensions -> Ordering
Extensions -> Extensions -> Extensions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Extensions -> Extensions -> Ordering
compare :: Extensions -> Extensions -> Ordering
$c< :: Extensions -> Extensions -> Bool
< :: Extensions -> Extensions -> Bool
$c<= :: Extensions -> Extensions -> Bool
<= :: Extensions -> Extensions -> Bool
$c> :: Extensions -> Extensions -> Bool
> :: Extensions -> Extensions -> Bool
$c>= :: Extensions -> Extensions -> Bool
>= :: Extensions -> Extensions -> Bool
$cmax :: Extensions -> Extensions -> Extensions
max :: Extensions -> Extensions -> Extensions
$cmin :: Extensions -> Extensions -> Extensions
min :: Extensions -> Extensions -> Extensions
Ord, Typeable Extensions
Typeable Extensions
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Extensions -> c Extensions)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Extensions)
-> (Extensions -> Constr)
-> (Extensions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Extensions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Extensions))
-> ((forall b. Data b => b -> b) -> Extensions -> Extensions)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Extensions -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Extensions -> r)
-> (forall u. (forall d. Data d => d -> u) -> Extensions -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Extensions -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Extensions -> m Extensions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Extensions -> m Extensions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Extensions -> m Extensions)
-> Data Extensions
Extensions -> Constr
Extensions -> DataType
(forall b. Data b => b -> b) -> Extensions -> Extensions
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Extensions -> u
forall u. (forall d. Data d => d -> u) -> Extensions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extensions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extensions -> c Extensions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extensions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extensions)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extensions -> c Extensions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Extensions -> c Extensions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extensions
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Extensions
$ctoConstr :: Extensions -> Constr
toConstr :: Extensions -> Constr
$cdataTypeOf :: Extensions -> DataType
dataTypeOf :: Extensions -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extensions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Extensions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extensions)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extensions)
$cgmapT :: (forall b. Data b => b -> b) -> Extensions -> Extensions
gmapT :: (forall b. Data b => b -> b) -> Extensions -> Extensions
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Extensions -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Extensions -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Extensions -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Extensions -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Extensions -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Extensions -> m Extensions
Data, Typeable, (forall x. Extensions -> Rep Extensions x)
-> (forall x. Rep Extensions x -> Extensions) -> Generic Extensions
forall x. Rep Extensions x -> Extensions
forall x. Extensions -> Rep Extensions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Extensions -> Rep Extensions x
from :: forall x. Extensions -> Rep Extensions x
$cto :: forall x. Rep Extensions x -> Extensions
to :: forall x. Rep Extensions x -> Extensions
Generic)

instance Semigroup Extensions where
  (Extensions Set Extension
a) <> :: Extensions -> Extensions -> Extensions
<> (Extensions Set Extension
b) = Set Extension -> Extensions
Extensions (Set Extension
a Set Extension -> Set Extension -> Set Extension
forall a. Semigroup a => a -> a -> a
<> Set Extension
b)
instance Monoid Extensions where
  mempty :: Extensions
mempty = Set Extension -> Extensions
Extensions Set Extension
forall a. Monoid a => a
mempty
  mappend :: Extensions -> Extensions -> Extensions
mappend = Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
(<>)

instance FromJSON Extensions where
  parseJSON :: Value -> Parser Extensions
parseJSON = ([Extension] -> Extensions)
-> Parser [Extension] -> Parser Extensions
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Extension] -> Extensions
extensionsFromList (Parser [Extension] -> Parser Extensions)
-> (Value -> Parser [Extension]) -> Value -> Parser Extensions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser [Extension]
forall a. FromJSON a => Value -> Parser a
parseJSON

instance ToJSON Extensions where
  toJSON :: Extensions -> Value
toJSON (Extensions Set Extension
exts) = Set Extension -> Value
forall a. ToJSON a => a -> Value
toJSON Set Extension
exts

-- | Reads a single extension from a string.
readExtension :: String -> Extension
readExtension :: String -> Extension
readExtension String
"lhs" = Extension
Ext_literate_haskell
readExtension String
name =
  case String -> Maybe Extension
forall a. Read a => String -> Maybe a
readMaybe (String
"Ext_" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name) of
    Just Extension
ext -> Extension
ext
    Maybe Extension
Nothing -> Text -> Extension
CustomExtension (String -> Text
T.pack String
name)

-- | Show an extension in human-readable form.
showExtension :: Extension -> T.Text
showExtension :: Extension -> Text
showExtension Extension
ext =
  case Extension
ext of
    CustomExtension Text
t -> Text
t
    Extension
_ -> Int -> Text -> Text
T.drop Int
4 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Extension -> String
forall a. Show a => a -> String
show Extension
ext

extensionsFromList :: [Extension] -> Extensions
extensionsFromList :: [Extension] -> Extensions
extensionsFromList = Set Extension -> Extensions
Extensions (Set Extension -> Extensions)
-> ([Extension] -> Set Extension) -> [Extension] -> Extensions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Extension] -> Set Extension
forall a. Ord a => [a] -> Set a
Set.fromList

extensionsToList :: Extensions -> [Extension]
extensionsToList :: Extensions -> [Extension]
extensionsToList (Extensions Set Extension
extset) = [Extension] -> [Extension]
forall a. Ord a => [a] -> [a]
sort ([Extension] -> [Extension]) -> [Extension] -> [Extension]
forall a b. (a -> b) -> a -> b
$ Set Extension -> [Extension]
forall a. Set a -> [a]
Set.toList Set Extension
extset

emptyExtensions :: Extensions
emptyExtensions :: Extensions
emptyExtensions = Set Extension -> Extensions
Extensions Set Extension
forall a. Monoid a => a
mempty

extensionEnabled :: Extension -> Extensions -> Bool
extensionEnabled :: Extension -> Extensions -> Bool
extensionEnabled Extension
x (Extensions Set Extension
exts) = Extension
x Extension -> Set Extension -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Extension
exts

enableExtension :: Extension -> Extensions -> Extensions
enableExtension :: Extension -> Extensions -> Extensions
enableExtension Extension
x (Extensions Set Extension
exts) = Set Extension -> Extensions
Extensions (Extension -> Set Extension -> Set Extension
forall a. Ord a => a -> Set a -> Set a
Set.insert Extension
x Set Extension
exts)

disableExtension :: Extension -> Extensions -> Extensions
disableExtension :: Extension -> Extensions -> Extensions
disableExtension Extension
x (Extensions Set Extension
exts) = Set Extension -> Extensions
Extensions (Extension -> Set Extension -> Set Extension
forall a. Ord a => a -> Set a -> Set a
Set.delete Extension
x Set Extension
exts)

-- | Removes the extensions in the second set from those in the first.
disableExtensions :: Extensions  -- ^ base set
                  -> Extensions  -- ^ extensions to remove
                  -> Extensions
disableExtensions :: Extensions -> Extensions -> Extensions
disableExtensions (Extensions Set Extension
base) (Extensions Set Extension
remove) = Set Extension -> Extensions
Extensions (Set Extension -> Extensions) -> Set Extension -> Extensions
forall a b. (a -> b) -> a -> b
$
  -- keep only those extensions that are in `base` but not in `remove`.
  Set Extension
base Set Extension -> Set Extension -> Set Extension
forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set Extension
remove

-- | Extensions to be used with pandoc-flavored markdown.
pandocExtensions :: Extensions
pandocExtensions :: Extensions
pandocExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_footnotes
  , Extension
Ext_inline_notes
  , Extension
Ext_pandoc_title_block
  , Extension
Ext_yaml_metadata_block
  , Extension
Ext_table_captions
  , Extension
Ext_implicit_figures
  , Extension
Ext_simple_tables
  , Extension
Ext_multiline_tables
  , Extension
Ext_grid_tables
  , Extension
Ext_pipe_tables
  , Extension
Ext_citations
  , Extension
Ext_raw_tex
  , Extension
Ext_raw_html
  , Extension
Ext_tex_math_dollars
  , Extension
Ext_latex_macros
  , Extension
Ext_fenced_code_blocks
  , Extension
Ext_fenced_code_attributes
  , Extension
Ext_backtick_code_blocks
  , Extension
Ext_inline_code_attributes
  , Extension
Ext_raw_attribute
  , Extension
Ext_markdown_in_html_blocks
  , Extension
Ext_native_divs
  , Extension
Ext_fenced_divs
  , Extension
Ext_native_spans
  , Extension
Ext_bracketed_spans
  , Extension
Ext_escaped_line_breaks
  , Extension
Ext_fancy_lists
  , Extension
Ext_startnum
  , Extension
Ext_definition_lists
  , Extension
Ext_example_lists
  , Extension
Ext_all_symbols_escapable
  , Extension
Ext_intraword_underscores
  , Extension
Ext_blank_before_blockquote
  , Extension
Ext_blank_before_header
  , Extension
Ext_space_in_atx_header
  , Extension
Ext_strikeout
  , Extension
Ext_superscript
  , Extension
Ext_subscript
  , Extension
Ext_task_lists
  , Extension
Ext_auto_identifiers
  , Extension
Ext_header_attributes
  , Extension
Ext_link_attributes
  , Extension
Ext_implicit_header_references
  , Extension
Ext_line_blocks
  , Extension
Ext_shortcut_reference_links
  , Extension
Ext_smart
  ]

-- | Extensions to be used with plain text output.
plainExtensions :: Extensions
plainExtensions :: Extensions
plainExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_table_captions
  , Extension
Ext_implicit_figures
  , Extension
Ext_simple_tables
  , Extension
Ext_multiline_tables
  , Extension
Ext_grid_tables
  , Extension
Ext_latex_macros
  , Extension
Ext_fancy_lists
  , Extension
Ext_startnum
  , Extension
Ext_definition_lists
  , Extension
Ext_example_lists
  , Extension
Ext_intraword_underscores
  , Extension
Ext_blank_before_blockquote
  , Extension
Ext_blank_before_header
  , Extension
Ext_strikeout
  ]

-- | Extensions to be used with PHP Markdown Extra.
phpMarkdownExtraExtensions :: Extensions
phpMarkdownExtraExtensions :: Extensions
phpMarkdownExtraExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_footnotes
  , Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_markdown_attribute
  , Extension
Ext_fenced_code_blocks
  , Extension
Ext_definition_lists
  , Extension
Ext_intraword_underscores
  , Extension
Ext_header_attributes
  , Extension
Ext_link_attributes
  , Extension
Ext_abbreviations
  , Extension
Ext_shortcut_reference_links
  , Extension
Ext_spaced_reference_links
  ]

-- | Extensions to be used with github-flavored markdown.
githubMarkdownExtensions :: Extensions
githubMarkdownExtensions :: Extensions
githubMarkdownExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_auto_identifiers
  , Extension
Ext_gfm_auto_identifiers
  , Extension
Ext_autolink_bare_uris
  , Extension
Ext_strikeout
  , Extension
Ext_task_lists
  , Extension
Ext_emoji
  , Extension
Ext_fenced_code_blocks
  , Extension
Ext_backtick_code_blocks
  ]

-- | Extensions to be used with multimarkdown.
multimarkdownExtensions :: Extensions
multimarkdownExtensions :: Extensions
multimarkdownExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_markdown_attribute
  , Extension
Ext_mmd_link_attributes
  -- , Ext_raw_tex
  -- Note: MMD's raw TeX syntax requires raw TeX to be
  -- enclosed in HTML comment
  , Extension
Ext_tex_math_double_backslash
  , Extension
Ext_tex_math_dollars
  , Extension
Ext_intraword_underscores
  , Extension
Ext_mmd_title_block
  , Extension
Ext_footnotes
  , Extension
Ext_definition_lists
  , Extension
Ext_all_symbols_escapable
  , Extension
Ext_implicit_header_references
  , Extension
Ext_shortcut_reference_links
  , Extension
Ext_auto_identifiers
  , Extension
Ext_mmd_header_identifiers
  , Extension
Ext_implicit_figures
  , Extension
Ext_short_subsuperscripts
  , Extension
Ext_subscript
  , Extension
Ext_superscript
  , Extension
Ext_backtick_code_blocks
  , Extension
Ext_spaced_reference_links
  -- So far only in dev version of mmd:
  , Extension
Ext_raw_attribute
  ]

-- | Language extensions to be used with strict markdown.
strictExtensions :: Extensions
strictExtensions :: Extensions
strictExtensions = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_raw_html
  , Extension
Ext_shortcut_reference_links
  , Extension
Ext_spaced_reference_links
  ]

-- | Default extensions from format-describing string.
getDefaultExtensions :: T.Text -> Extensions
getDefaultExtensions :: Text -> Extensions
getDefaultExtensions Text
"markdown_strict"   = Extensions
strictExtensions
getDefaultExtensions Text
"markdown_phpextra" = Extensions
phpMarkdownExtraExtensions
getDefaultExtensions Text
"markdown_mmd"      = Extensions
multimarkdownExtensions
getDefaultExtensions Text
"markdown_github"   = Extensions
githubMarkdownExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
  [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_all_symbols_escapable
    , Extension
Ext_backtick_code_blocks
    , Extension
Ext_fenced_code_blocks
    , Extension
Ext_space_in_atx_header
    , Extension
Ext_intraword_underscores
    , Extension
Ext_lists_without_preceding_blankline
    , Extension
Ext_shortcut_reference_links
    ]
getDefaultExtensions Text
"markdown"          = Extensions
pandocExtensions
getDefaultExtensions Text
"ipynb"             =
  [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_all_symbols_escapable
    , Extension
Ext_pipe_tables
    , Extension
Ext_raw_html
    , Extension
Ext_fenced_code_blocks
    , Extension
Ext_auto_identifiers
    , Extension
Ext_gfm_auto_identifiers
    , Extension
Ext_backtick_code_blocks
    , Extension
Ext_autolink_bare_uris
    , Extension
Ext_space_in_atx_header
    , Extension
Ext_intraword_underscores
    , Extension
Ext_strikeout
    , Extension
Ext_task_lists
    , Extension
Ext_lists_without_preceding_blankline
    , Extension
Ext_shortcut_reference_links
    , Extension
Ext_tex_math_dollars
    ]
getDefaultExtensions Text
"muse"            = [Extension] -> Extensions
extensionsFromList
                                           [Extension
Ext_amuse,
                                            Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"plain"           = Extensions
plainExtensions
getDefaultExtensions Text
"gfm"             = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_auto_identifiers
  , Extension
Ext_gfm_auto_identifiers
  , Extension
Ext_autolink_bare_uris
  , Extension
Ext_strikeout
  , Extension
Ext_task_lists
  , Extension
Ext_emoji
  , Extension
Ext_yaml_metadata_block
  , Extension
Ext_footnotes
  , Extension
Ext_tex_math_dollars
  ]
getDefaultExtensions Text
"commonmark"      = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_raw_html]
getDefaultExtensions Text
"commonmark_x"    = [Extension] -> Extensions
extensionsFromList
  [ Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_gfm_auto_identifiers
  , Extension
Ext_strikeout
  , Extension
Ext_task_lists
  , Extension
Ext_emoji
  , Extension
Ext_pipe_tables
  , Extension
Ext_raw_html
  , Extension
Ext_smart
  , Extension
Ext_tex_math_dollars
  , Extension
Ext_superscript
  , Extension
Ext_subscript
  , Extension
Ext_definition_lists
  , Extension
Ext_footnotes
  , Extension
Ext_fancy_lists
  , Extension
Ext_fenced_divs
  , Extension
Ext_bracketed_spans
  , Extension
Ext_raw_attribute
  , Extension
Ext_implicit_header_references
  , Extension
Ext_attributes
  , Extension
Ext_yaml_metadata_block
  ]
getDefaultExtensions Text
"org"             = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_citations,
                                           Extension
Ext_task_lists,
                                           Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"html"            = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_auto_identifiers,
                                           Extension
Ext_native_divs,
                                           Extension
Ext_line_blocks,
                                           Extension
Ext_native_spans]
getDefaultExtensions Text
"html4"           = Text -> Extensions
getDefaultExtensions Text
"html"
getDefaultExtensions Text
"html5"           = Text -> Extensions
getDefaultExtensions Text
"html"
getDefaultExtensions Text
"epub"            = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_raw_html,
                                           Extension
Ext_native_divs,
                                           Extension
Ext_native_spans,
                                           Extension
Ext_epub_html_exts]
getDefaultExtensions Text
"epub2"           = Text -> Extensions
getDefaultExtensions Text
"epub"
getDefaultExtensions Text
"epub3"           = Text -> Extensions
getDefaultExtensions Text
"epub"
getDefaultExtensions Text
"latex"           = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_smart,
                                           Extension
Ext_latex_macros,
                                           Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"beamer"          = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_smart,
                                           Extension
Ext_latex_macros,
                                           Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"context"         = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_smart,
                                           Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"textile"         = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_old_dashes,
                                           Extension
Ext_smart,
                                           Extension
Ext_raw_html,
                                           Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"jats"            = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_auto_identifiers]
getDefaultExtensions Text
"jats_archiving"  = Text -> Extensions
getDefaultExtensions Text
"jats"
getDefaultExtensions Text
"jats_publishing" = Text -> Extensions
getDefaultExtensions Text
"jats"
getDefaultExtensions Text
"jats_articleauthoring" = Text -> Extensions
getDefaultExtensions Text
"jats"
getDefaultExtensions Text
"opml"            = Extensions
pandocExtensions -- affects notes
getDefaultExtensions Text
"markua"          = [Extension] -> Extensions
extensionsFromList
                                          []
getDefaultExtensions Text
"typst"           = [Extension] -> Extensions
extensionsFromList [Extension
Ext_citations]
getDefaultExtensions Text
_                 = [Extension] -> Extensions
extensionsFromList
                                          [Extension
Ext_auto_identifiers]


-- | Get all valid extensions for a format. This is used
-- mainly in checking format specifications for validity.
getAllExtensions :: T.Text -> Extensions
getAllExtensions :: Text -> Extensions
getAllExtensions Text
f = Extensions
universalExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<> Text -> Extensions
forall {t}. (Eq t, IsString t) => t -> Extensions
getAll Text
f
 where
  autoIdExtensions :: Extensions
autoIdExtensions           = [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_auto_identifiers
    , Extension
Ext_gfm_auto_identifiers
    , Extension
Ext_ascii_identifiers
    ]
  universalExtensions :: Extensions
universalExtensions        = [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_east_asian_line_breaks ]
  allMarkdownExtensions :: Extensions
allMarkdownExtensions =
    Extensions
pandocExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<> Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
      [Extension] -> Extensions
extensionsFromList
       [ Extension
Ext_old_dashes
       , Extension
Ext_angle_brackets_escapable
       , Extension
Ext_lists_without_preceding_blankline
       , Extension
Ext_four_space_rule
       , Extension
Ext_spaced_reference_links
       , Extension
Ext_hard_line_breaks
       , Extension
Ext_ignore_line_breaks
       , Extension
Ext_east_asian_line_breaks
       , Extension
Ext_emoji
       , Extension
Ext_tex_math_single_backslash
       , Extension
Ext_tex_math_double_backslash
       , Extension
Ext_markdown_attribute
       , Extension
Ext_mmd_title_block
       , Extension
Ext_abbreviations
       , Extension
Ext_autolink_bare_uris
       , Extension
Ext_mark
       , Extension
Ext_mmd_link_attributes
       , Extension
Ext_mmd_header_identifiers
       , Extension
Ext_compact_definition_lists
       , Extension
Ext_gutenberg
       , Extension
Ext_smart
       , Extension
Ext_literate_haskell
       , Extension
Ext_short_subsuperscripts
       , Extension
Ext_rebase_relative_paths
       , Extension
Ext_wikilinks_title_after_pipe
       , Extension
Ext_wikilinks_title_before_pipe
       ]
  getAll :: t -> Extensions
getAll t
"markdown_strict"   = Extensions
allMarkdownExtensions
  getAll t
"markdown_phpextra" = Extensions
allMarkdownExtensions
  getAll t
"markdown_mmd"      = Extensions
allMarkdownExtensions
  getAll t
"markdown_github"   = Extensions
allMarkdownExtensions
  getAll t
"markdown"          = Extensions
allMarkdownExtensions
  getAll t
"ipynb"             = Extensions
allMarkdownExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<> [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_raw_markdown ]
  getAll t
"docx"            = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<> [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_empty_paragraphs
    , Extension
Ext_native_numbering
    , Extension
Ext_styles
    , Extension
Ext_citations
    ]
  getAll t
"opendocument"    = [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_empty_paragraphs
    , Extension
Ext_native_numbering
    , Extension
Ext_xrefs_name
    , Extension
Ext_xrefs_number
    ]
  getAll t
"odt"             = t -> Extensions
getAll t
"opendocument" Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<> Extensions
autoIdExtensions
  getAll t
"muse"            = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_amuse ]
  getAll t
"asciidoc"        = Extensions
autoIdExtensions
  getAll t
"plain"           = Extensions
allMarkdownExtensions
  getAll t
"gfm"             = t -> Extensions
getAll t
"commonmark"
  getAll t
"commonmark"      =
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_gfm_auto_identifiers
    , Extension
Ext_ascii_identifiers
    , Extension
Ext_pipe_tables
    , Extension
Ext_autolink_bare_uris
    , Extension
Ext_strikeout
    , Extension
Ext_task_lists
    , Extension
Ext_emoji
    , Extension
Ext_raw_html
    , Extension
Ext_implicit_figures
    , Extension
Ext_hard_line_breaks
    , Extension
Ext_smart
    , Extension
Ext_tex_math_dollars
    , Extension
Ext_superscript
    , Extension
Ext_subscript
    , Extension
Ext_definition_lists
    , Extension
Ext_footnotes
    , Extension
Ext_fancy_lists
    , Extension
Ext_fenced_divs
    , Extension
Ext_bracketed_spans
    , Extension
Ext_raw_attribute
    , Extension
Ext_implicit_header_references
    , Extension
Ext_attributes
    , Extension
Ext_sourcepos
    , Extension
Ext_wikilinks_title_after_pipe
    , Extension
Ext_wikilinks_title_before_pipe
    , Extension
Ext_yaml_metadata_block
    , Extension
Ext_rebase_relative_paths
    ]
  getAll t
"commonmark_x"    = t -> Extensions
getAll t
"commonmark"
  getAll t
"org"             = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_citations
    , Extension
Ext_smart
    , Extension
Ext_fancy_lists
    , Extension
Ext_task_lists
    ]
  getAll t
"html"            = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_native_divs
    , Extension
Ext_line_blocks
    , Extension
Ext_native_spans
    , Extension
Ext_empty_paragraphs
    , Extension
Ext_raw_html
    , Extension
Ext_raw_tex
    , Extension
Ext_task_lists
    , Extension
Ext_tex_math_dollars
    , Extension
Ext_tex_math_single_backslash
    , Extension
Ext_tex_math_double_backslash
    , Extension
Ext_literate_haskell
    , Extension
Ext_epub_html_exts
    , Extension
Ext_smart
    ]
  getAll t
"html4"           = t -> Extensions
getAll t
"html"
  getAll t
"html5"           = t -> Extensions
getAll t
"html"
  getAll t
"epub"            = t -> Extensions
getAll t
"html"
  getAll t
"epub2"           = t -> Extensions
getAll t
"epub"
  getAll t
"epub3"           = t -> Extensions
getAll t
"epub"
  getAll t
"latex"           = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_smart
    , Extension
Ext_latex_macros
    , Extension
Ext_raw_tex
    , Extension
Ext_task_lists
    , Extension
Ext_literate_haskell
    ]
  getAll t
"beamer"          = t -> Extensions
getAll t
"latex"
  getAll t
"context"         = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_smart
    , Extension
Ext_raw_tex
    , Extension
Ext_ntb
    , Extension
Ext_tagging
    ]
  getAll t
"textile"         = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_old_dashes
    , Extension
Ext_smart
    , Extension
Ext_raw_tex
    ]
  getAll t
"jats"            =
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_auto_identifiers
    , Extension
Ext_element_citations
    ]
  getAll t
"jats_archiving"  = t -> Extensions
getAll t
"jats"
  getAll t
"jats_publishing" = t -> Extensions
getAll t
"jats"
  getAll t
"jats_articleauthoring" = t -> Extensions
getAll t
"jats"
  getAll t
"opml"            = Extensions
allMarkdownExtensions -- affects notes
  getAll t
"twiki"           = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_smart ]
  getAll t
"vimwiki"         = Extensions
autoIdExtensions
  getAll t
"dokuwiki"        = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_tex_math_dollars ]
  getAll t
"tikiwiki"        = Extensions
autoIdExtensions
  getAll t
"rst"             = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_smart
    , Extension
Ext_literate_haskell
    ]
  getAll t
"mediawiki"       = Extensions
autoIdExtensions Extensions -> Extensions -> Extensions
forall a. Semigroup a => a -> a -> a
<>
    [Extension] -> Extensions
extensionsFromList
    [ Extension
Ext_smart ]
  getAll t
"typst"           = [Extension] -> Extensions
extensionsFromList [Extension
Ext_citations]
  getAll t
_                 = Extensions
forall a. Monoid a => a
mempty