| Copyright | Copyright (C) 2012-2022 John MacFarlane | 
|---|---|
| License | GNU GPL, version 2 or above | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Text.Pandoc.Options
Description
Data structures and functions for representing parser and writer options.
Synopsis
- module Text.Pandoc.Extensions
 - data ReaderOptions = ReaderOptions {}
 - data HTMLMathMethod
 - data CiteMethod
 - data ObfuscationMethod
 - data HTMLSlideVariant
 - data EPUBVersion
 - data WrapOption
 - data TopLevelDivision
 - data WriterOptions = WriterOptions {
- writerTemplate :: Maybe (Template Text)
 - writerVariables :: Context Text
 - writerTabStop :: Int
 - writerTableOfContents :: Bool
 - writerIncremental :: Bool
 - writerHTMLMathMethod :: HTMLMathMethod
 - writerNumberSections :: Bool
 - writerNumberOffset :: [Int]
 - writerSectionDivs :: Bool
 - writerExtensions :: Extensions
 - writerReferenceLinks :: Bool
 - writerDpi :: Int
 - writerWrapText :: WrapOption
 - writerColumns :: Int
 - writerEmailObfuscation :: ObfuscationMethod
 - writerIdentifierPrefix :: Text
 - writerCiteMethod :: CiteMethod
 - writerHtmlQTags :: Bool
 - writerSlideLevel :: Maybe Int
 - writerTopLevelDivision :: TopLevelDivision
 - writerListings :: Bool
 - writerHighlightStyle :: Maybe Style
 - writerSetextHeaders :: Bool
 - writerEpubSubdirectory :: Text
 - writerEpubMetadata :: Maybe Text
 - writerEpubFonts :: [FilePath]
 - writerEpubChapterLevel :: Int
 - writerTOCDepth :: Int
 - writerReferenceDoc :: Maybe FilePath
 - writerReferenceLocation :: ReferenceLocation
 - writerSyntaxMap :: SyntaxMap
 - writerPreferAscii :: Bool
 
 - data TrackChanges
 - data ReferenceLocation
 - def :: Default a => a
 - isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
 - defaultMathJaxURL :: Text
 - defaultKaTeXURL :: Text
 
Documentation
module Text.Pandoc.Extensions
data ReaderOptions Source #
Constructors
| ReaderOptions | |
Fields 
  | |
Instances
data HTMLMathMethod Source #
Instances
data CiteMethod Source #
Instances
| Data CiteMethod Source # | |
Defined in Text.Pandoc.Options 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 :: forall r r'. (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 #  | |
| Generic CiteMethod Source # | |
Defined in Text.Pandoc.Options Associated Types type Rep CiteMethod :: Type -> Type #  | |
| Read CiteMethod Source # | |
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS CiteMethod # readList :: ReadS [CiteMethod] # readPrec :: ReadPrec CiteMethod # readListPrec :: ReadPrec [CiteMethod] #  | |
| Show CiteMethod Source # | |
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> CiteMethod -> ShowS # show :: CiteMethod -> String # showList :: [CiteMethod] -> ShowS #  | |
| Eq CiteMethod Source # | |
Defined in Text.Pandoc.Options  | |
| FromJSON CiteMethod Source # | |
Defined in Text.Pandoc.Options  | |
| ToJSON CiteMethod Source # | |
Defined in Text.Pandoc.Options Methods toJSON :: CiteMethod -> Value toEncoding :: CiteMethod -> Encoding toJSONList :: [CiteMethod] -> Value toEncodingList :: [CiteMethod] -> Encoding  | |
| type Rep CiteMethod Source # | |
Defined in Text.Pandoc.Options type Rep CiteMethod = D1 ('MetaData "CiteMethod" "Text.Pandoc.Options" "pandoc-2.19.2-inplace" 'False) (C1 ('MetaCons "Citeproc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Natbib" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Biblatex" 'PrefixI 'False) (U1 :: Type -> Type)))  | |
data ObfuscationMethod Source #
Methods for obfuscating email addresses in HTML.
Constructors
| NoObfuscation | |
| ReferenceObfuscation | |
| JavascriptObfuscation | 
Instances
data HTMLSlideVariant Source #
Varieties of HTML slide shows.
Constructors
| S5Slides | |
| SlidySlides | |
| SlideousSlides | |
| DZSlides | |
| RevealJsSlides | |
| NoSlides | 
Instances
data EPUBVersion Source #
Instances
| Data EPUBVersion Source # | |
Defined in Text.Pandoc.Options 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 :: forall r r'. (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 #  | |
| Generic EPUBVersion Source # | |
Defined in Text.Pandoc.Options Associated Types type Rep EPUBVersion :: Type -> Type #  | |
| Read EPUBVersion Source # | |
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS EPUBVersion # readList :: ReadS [EPUBVersion] # readPrec :: ReadPrec EPUBVersion # readListPrec :: ReadPrec [EPUBVersion] #  | |
| Show EPUBVersion Source # | |
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> EPUBVersion -> ShowS # show :: EPUBVersion -> String # showList :: [EPUBVersion] -> ShowS #  | |
| Eq EPUBVersion Source # | |
Defined in Text.Pandoc.Options  | |
| type Rep EPUBVersion Source # | |
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
| Data WrapOption Source # | |
Defined in Text.Pandoc.Options 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 :: forall r r'. (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 #  | |
| Generic WrapOption Source # | |
Defined in Text.Pandoc.Options Associated Types type Rep WrapOption :: Type -> Type #  | |
| Read WrapOption Source # | |
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS WrapOption # readList :: ReadS [WrapOption] # readPrec :: ReadPrec WrapOption # readListPrec :: ReadPrec [WrapOption] #  | |
| Show WrapOption Source # | |
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> WrapOption -> ShowS # show :: WrapOption -> String # showList :: [WrapOption] -> ShowS #  | |
| Eq WrapOption Source # | |
Defined in Text.Pandoc.Options  | |
| FromJSON WrapOption Source # | |
Defined in Text.Pandoc.Options  | |
| ToJSON WrapOption Source # | |
Defined in Text.Pandoc.Options Methods toJSON :: WrapOption -> Value toEncoding :: WrapOption -> Encoding toJSONList :: [WrapOption] -> Value toEncodingList :: [WrapOption] -> Encoding  | |
| type Rep WrapOption Source # | |
Defined in Text.Pandoc.Options type Rep WrapOption = D1 ('MetaData "WrapOption" "Text.Pandoc.Options" "pandoc-2.19.2-inplace" 'False) (C1 ('MetaCons "WrapAuto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WrapNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WrapPreserve" 'PrefixI 'False) (U1 :: Type -> Type)))  | |
data TopLevelDivision Source #
Options defining the type of top-level headers.
Constructors
| TopLevelPart | Top-level headers become parts  | 
| TopLevelChapter | Top-level headers become chapters  | 
| TopLevelSection | Top-level headers become sections  | 
| TopLevelDefault | Top-level type is determined via heuristics  | 
Instances
data WriterOptions Source #
Options for writers
Constructors
| WriterOptions | |
Fields 
  | |
Instances
data TrackChanges Source #
Options for accepting or rejecting MS Word track-changes.
Constructors
| AcceptChanges | |
| RejectChanges | |
| AllChanges | 
Instances
| Data TrackChanges Source # | |
Defined in Text.Pandoc.Options 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 :: forall r r'. (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 #  | |
| Generic TrackChanges Source # | |
Defined in Text.Pandoc.Options Associated Types type Rep TrackChanges :: Type -> Type #  | |
| Read TrackChanges Source # | |
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS TrackChanges # readList :: ReadS [TrackChanges] #  | |
| Show TrackChanges Source # | |
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> TrackChanges -> ShowS # show :: TrackChanges -> String # showList :: [TrackChanges] -> ShowS #  | |
| Eq TrackChanges Source # | |
Defined in Text.Pandoc.Options  | |
| FromJSON TrackChanges Source # | |
Defined in Text.Pandoc.Options  | |
| ToJSON TrackChanges Source # | |
Defined in Text.Pandoc.Options Methods toJSON :: TrackChanges -> Value toEncoding :: TrackChanges -> Encoding toJSONList :: [TrackChanges] -> Value toEncodingList :: [TrackChanges] -> Encoding  | |
| type Rep TrackChanges Source # | |
Defined in Text.Pandoc.Options type Rep TrackChanges = D1 ('MetaData "TrackChanges" "Text.Pandoc.Options" "pandoc-2.19.2-inplace" 'False) (C1 ('MetaCons "AcceptChanges" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RejectChanges" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllChanges" 'PrefixI 'False) (U1 :: Type -> Type)))  | |
data ReferenceLocation Source #
Locations for footnotes and references in markdown output
Constructors
| EndOfBlock | End of block  | 
| EndOfSection | prior to next section header (or end of document)  | 
| EndOfDocument | at end of document  |