Copyright | Copyright (C) 2012-2024 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
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
- writerListOfFigures :: Bool
- writerListOfTables :: 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
- writerListTables :: Bool
- writerEpubSubdirectory :: Text
- writerEpubMetadata :: Maybe Text
- writerEpubFonts :: [FilePath]
- writerEpubTitlePage :: Bool
- writerSplitLevel :: Int
- writerChunkTemplate :: PathTemplate
- writerTOCDepth :: Int
- writerReferenceDoc :: Maybe FilePath
- writerReferenceLocation :: ReferenceLocation
- writerFigureCaptionPosition :: CaptionPosition
- writerTableCaptionPosition :: CaptionPosition
- writerSyntaxMap :: SyntaxMap
- writerPreferAscii :: Bool
- writerLinkImages :: Bool
- data TrackChanges
- data ReferenceLocation
- data CaptionPosition
- 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
FromJSON HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser HTMLMathMethod # parseJSONList :: Value -> Parser [HTMLMathMethod] # | |||||
ToJSON HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: HTMLMathMethod -> Value # toEncoding :: HTMLMathMethod -> Encoding # toJSONList :: [HTMLMathMethod] -> Value # toEncodingList :: [HTMLMathMethod] -> Encoding # omitField :: HTMLMathMethod -> Bool # | |||||
Data HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HTMLMathMethod -> c HTMLMathMethod # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HTMLMathMethod # toConstr :: HTMLMathMethod -> Constr # dataTypeOf :: HTMLMathMethod -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HTMLMathMethod) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HTMLMathMethod) # gmapT :: (forall b. Data b => b -> b) -> HTMLMathMethod -> HTMLMathMethod # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HTMLMathMethod -> r # gmapQ :: (forall d. Data d => d -> u) -> HTMLMathMethod -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HTMLMathMethod -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HTMLMathMethod -> m HTMLMathMethod # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HTMLMathMethod -> m HTMLMathMethod # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HTMLMathMethod -> m HTMLMathMethod # | |||||
Generic HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: HTMLMathMethod -> Rep HTMLMathMethod x # to :: Rep HTMLMathMethod x -> HTMLMathMethod # | |||||
Read HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS HTMLMathMethod # readList :: ReadS [HTMLMathMethod] # | |||||
Show HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> HTMLMathMethod -> ShowS # show :: HTMLMathMethod -> String # showList :: [HTMLMathMethod] -> ShowS # | |||||
Eq HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: HTMLMathMethod -> HTMLMathMethod -> Bool # (/=) :: HTMLMathMethod -> HTMLMathMethod -> Bool # | |||||
type Rep HTMLMathMethod Source # | |||||
Defined in Text.Pandoc.Options type Rep HTMLMathMethod = D1 ('MetaData "HTMLMathMethod" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) ((C1 ('MetaCons "PlainMath" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebTeX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "GladTeX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MathML" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MathJax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "KaTeX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) |
data CiteMethod Source #
Instances
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 # omitField :: CiteMethod -> Bool # | |||||
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
| |||||
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 | |||||
type Rep CiteMethod Source # | |||||
Defined in Text.Pandoc.Options type Rep CiteMethod = D1 ('MetaData "CiteMethod" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" '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
FromJSON ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser ObfuscationMethod # parseJSONList :: Value -> Parser [ObfuscationMethod] # | |||||
ToJSON ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: ObfuscationMethod -> Value # toEncoding :: ObfuscationMethod -> Encoding # toJSONList :: [ObfuscationMethod] -> Value # toEncodingList :: [ObfuscationMethod] -> Encoding # omitField :: ObfuscationMethod -> Bool # | |||||
Data ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObfuscationMethod -> c ObfuscationMethod # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObfuscationMethod # toConstr :: ObfuscationMethod -> Constr # dataTypeOf :: ObfuscationMethod -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObfuscationMethod) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObfuscationMethod) # gmapT :: (forall b. Data b => b -> b) -> ObfuscationMethod -> ObfuscationMethod # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObfuscationMethod -> r # gmapQ :: (forall d. Data d => d -> u) -> ObfuscationMethod -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObfuscationMethod -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObfuscationMethod -> m ObfuscationMethod # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObfuscationMethod -> m ObfuscationMethod # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObfuscationMethod -> m ObfuscationMethod # | |||||
Generic ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: ObfuscationMethod -> Rep ObfuscationMethod x # to :: Rep ObfuscationMethod x -> ObfuscationMethod # | |||||
Read ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS ObfuscationMethod # readList :: ReadS [ObfuscationMethod] # | |||||
Show ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> ObfuscationMethod -> ShowS # show :: ObfuscationMethod -> String # showList :: [ObfuscationMethod] -> ShowS # | |||||
Eq ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: ObfuscationMethod -> ObfuscationMethod -> Bool # (/=) :: ObfuscationMethod -> ObfuscationMethod -> Bool # | |||||
type Rep ObfuscationMethod Source # | |||||
Defined in Text.Pandoc.Options type Rep ObfuscationMethod = D1 ('MetaData "ObfuscationMethod" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) (C1 ('MetaCons "NoObfuscation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ReferenceObfuscation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavascriptObfuscation" 'PrefixI 'False) (U1 :: Type -> Type))) |
data HTMLSlideVariant Source #
Varieties of HTML slide shows.
Constructors
S5Slides | |
SlidySlides | |
SlideousSlides | |
DZSlides | |
RevealJsSlides | |
NoSlides |
Instances
FromJSON HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser HTMLSlideVariant # parseJSONList :: Value -> Parser [HTMLSlideVariant] # | |||||
ToJSON HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: HTMLSlideVariant -> Value # toEncoding :: HTMLSlideVariant -> Encoding # toJSONList :: [HTMLSlideVariant] -> Value # toEncodingList :: [HTMLSlideVariant] -> Encoding # omitField :: HTMLSlideVariant -> Bool # | |||||
Data HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HTMLSlideVariant -> c HTMLSlideVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HTMLSlideVariant # toConstr :: HTMLSlideVariant -> Constr # dataTypeOf :: HTMLSlideVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HTMLSlideVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HTMLSlideVariant) # gmapT :: (forall b. Data b => b -> b) -> HTMLSlideVariant -> HTMLSlideVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HTMLSlideVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> HTMLSlideVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HTMLSlideVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HTMLSlideVariant -> m HTMLSlideVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HTMLSlideVariant -> m HTMLSlideVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HTMLSlideVariant -> m HTMLSlideVariant # | |||||
Generic HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: HTMLSlideVariant -> Rep HTMLSlideVariant x # to :: Rep HTMLSlideVariant x -> HTMLSlideVariant # | |||||
Read HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS HTMLSlideVariant # readList :: ReadS [HTMLSlideVariant] # | |||||
Show HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> HTMLSlideVariant -> ShowS # show :: HTMLSlideVariant -> String # showList :: [HTMLSlideVariant] -> ShowS # | |||||
Eq HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: HTMLSlideVariant -> HTMLSlideVariant -> Bool # (/=) :: HTMLSlideVariant -> HTMLSlideVariant -> Bool # | |||||
type Rep HTMLSlideVariant Source # | |||||
Defined in Text.Pandoc.Options type Rep HTMLSlideVariant = D1 ('MetaData "HTMLSlideVariant" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) ((C1 ('MetaCons "S5Slides" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SlidySlides" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SlideousSlides" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DZSlides" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RevealJsSlides" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoSlides" 'PrefixI 'False) (U1 :: Type -> Type)))) |
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
| |||||
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
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 # omitField :: WrapOption -> Bool # | |||||
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
| |||||
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 | |||||
type Rep WrapOption Source # | |||||
Defined in Text.Pandoc.Options type Rep WrapOption = D1 ('MetaData "WrapOption" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" '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
FromJSON TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser TopLevelDivision # parseJSONList :: Value -> Parser [TopLevelDivision] # | |||||
ToJSON TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: TopLevelDivision -> Value # toEncoding :: TopLevelDivision -> Encoding # toJSONList :: [TopLevelDivision] -> Value # toEncodingList :: [TopLevelDivision] -> Encoding # omitField :: TopLevelDivision -> Bool # | |||||
Data TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TopLevelDivision -> c TopLevelDivision # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TopLevelDivision # toConstr :: TopLevelDivision -> Constr # dataTypeOf :: TopLevelDivision -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TopLevelDivision) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopLevelDivision) # gmapT :: (forall b. Data b => b -> b) -> TopLevelDivision -> TopLevelDivision # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelDivision -> r # gmapQ :: (forall d. Data d => d -> u) -> TopLevelDivision -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TopLevelDivision -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TopLevelDivision -> m TopLevelDivision # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelDivision -> m TopLevelDivision # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelDivision -> m TopLevelDivision # | |||||
Generic TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: TopLevelDivision -> Rep TopLevelDivision x # to :: Rep TopLevelDivision x -> TopLevelDivision # | |||||
Read TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS TopLevelDivision # readList :: ReadS [TopLevelDivision] # | |||||
Show TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> TopLevelDivision -> ShowS # show :: TopLevelDivision -> String # showList :: [TopLevelDivision] -> ShowS # | |||||
Eq TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: TopLevelDivision -> TopLevelDivision -> Bool # (/=) :: TopLevelDivision -> TopLevelDivision -> Bool # | |||||
type Rep TopLevelDivision Source # | |||||
Defined in Text.Pandoc.Options type Rep TopLevelDivision = D1 ('MetaData "TopLevelDivision" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) ((C1 ('MetaCons "TopLevelPart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TopLevelChapter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TopLevelSection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TopLevelDefault" 'PrefixI 'False) (U1 :: Type -> Type))) |
data WriterOptions Source #
Options for writers
Constructors
WriterOptions | |
Fields
|
Instances
Data WriterOptions Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriterOptions -> c WriterOptions # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriterOptions # toConstr :: WriterOptions -> Constr # dataTypeOf :: WriterOptions -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WriterOptions) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriterOptions) # gmapT :: (forall b. Data b => b -> b) -> WriterOptions -> WriterOptions # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriterOptions -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriterOptions -> r # gmapQ :: (forall d. Data d => d -> u) -> WriterOptions -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WriterOptions -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriterOptions -> m WriterOptions # | |||||
Generic WriterOptions Source # | |||||
Defined in Text.Pandoc.Options Associated Types
| |||||
Show WriterOptions Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> WriterOptions -> ShowS # show :: WriterOptions -> String # showList :: [WriterOptions] -> ShowS # | |||||
Default WriterOptions Source # | |||||
Defined in Text.Pandoc.Options Methods def :: WriterOptions # | |||||
type Rep WriterOptions Source # | |||||
Defined in Text.Pandoc.Options type Rep WriterOptions = D1 ('MetaData "WriterOptions" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) (C1 ('MetaCons "WriterOptions" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "writerTemplate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Template Text))) :*: S1 ('MetaSel ('Just "writerVariables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Context Text))) :*: (S1 ('MetaSel ('Just "writerTabStop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "writerTableOfContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerListOfFigures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "writerListOfTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerIncremental") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "writerHTMLMathMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HTMLMathMethod) :*: (S1 ('MetaSel ('Just "writerNumberSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerNumberOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]))))) :*: (((S1 ('MetaSel ('Just "writerSectionDivs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Extensions)) :*: (S1 ('MetaSel ('Just "writerReferenceLinks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "writerDpi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "writerWrapText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WrapOption)))) :*: ((S1 ('MetaSel ('Just "writerColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "writerEmailObfuscation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObfuscationMethod)) :*: (S1 ('MetaSel ('Just "writerIdentifierPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "writerCiteMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CiteMethod) :*: S1 ('MetaSel ('Just "writerHtmlQTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) :*: ((((S1 ('MetaSel ('Just "writerSlideLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "writerTopLevelDivision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TopLevelDivision)) :*: (S1 ('MetaSel ('Just "writerListings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "writerHighlightStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Style)) :*: S1 ('MetaSel ('Just "writerSetextHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "writerListTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerEpubSubdirectory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "writerEpubMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "writerEpubFonts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "writerEpubTitlePage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: (((S1 ('MetaSel ('Just "writerSplitLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "writerChunkTemplate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PathTemplate)) :*: (S1 ('MetaSel ('Just "writerTOCDepth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "writerReferenceDoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "writerReferenceLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReferenceLocation)))) :*: ((S1 ('MetaSel ('Just "writerFigureCaptionPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CaptionPosition) :*: S1 ('MetaSel ('Just "writerTableCaptionPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CaptionPosition)) :*: (S1 ('MetaSel ('Just "writerSyntaxMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SyntaxMap) :*: (S1 ('MetaSel ('Just "writerPreferAscii") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writerLinkImages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))))) |
data TrackChanges Source #
Options for accepting or rejecting MS Word track-changes.
Constructors
AcceptChanges | |
RejectChanges | |
AllChanges |
Instances
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 # omitField :: TrackChanges -> Bool # | |||||
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
| |||||
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 | |||||
type Rep TrackChanges Source # | |||||
Defined in Text.Pandoc.Options type Rep TrackChanges = D1 ('MetaData "TrackChanges" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" '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 |
Instances
FromJSON ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser ReferenceLocation # parseJSONList :: Value -> Parser [ReferenceLocation] # | |||||
ToJSON ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: ReferenceLocation -> Value # toEncoding :: ReferenceLocation -> Encoding # toJSONList :: [ReferenceLocation] -> Value # toEncodingList :: [ReferenceLocation] -> Encoding # omitField :: ReferenceLocation -> Bool # | |||||
Data ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReferenceLocation -> c ReferenceLocation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReferenceLocation # toConstr :: ReferenceLocation -> Constr # dataTypeOf :: ReferenceLocation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReferenceLocation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReferenceLocation) # gmapT :: (forall b. Data b => b -> b) -> ReferenceLocation -> ReferenceLocation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReferenceLocation -> r # gmapQ :: (forall d. Data d => d -> u) -> ReferenceLocation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ReferenceLocation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReferenceLocation -> m ReferenceLocation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReferenceLocation -> m ReferenceLocation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReferenceLocation -> m ReferenceLocation # | |||||
Generic ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: ReferenceLocation -> Rep ReferenceLocation x # to :: Rep ReferenceLocation x -> ReferenceLocation # | |||||
Read ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS ReferenceLocation # readList :: ReadS [ReferenceLocation] # | |||||
Show ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> ReferenceLocation -> ShowS # show :: ReferenceLocation -> String # showList :: [ReferenceLocation] -> ShowS # | |||||
Eq ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: ReferenceLocation -> ReferenceLocation -> Bool # (/=) :: ReferenceLocation -> ReferenceLocation -> Bool # | |||||
type Rep ReferenceLocation Source # | |||||
Defined in Text.Pandoc.Options type Rep ReferenceLocation = D1 ('MetaData "ReferenceLocation" "Text.Pandoc.Options" "pandoc-3.7.0.1-7RIEUq3CJpwBTELIbnz3b6" 'False) (C1 ('MetaCons "EndOfBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndOfSection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndOfDocument" 'PrefixI 'False) (U1 :: Type -> Type))) |
data CaptionPosition Source #
Positions for figure and table captions
Constructors
CaptionAbove | above figure or table |
CaptionBelow | below figure or table |
Instances
FromJSON CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods parseJSON :: Value -> Parser CaptionPosition # parseJSONList :: Value -> Parser [CaptionPosition] # | |||||
ToJSON CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods toJSON :: CaptionPosition -> Value # toEncoding :: CaptionPosition -> Encoding # toJSONList :: [CaptionPosition] -> Value # toEncodingList :: [CaptionPosition] -> Encoding # omitField :: CaptionPosition -> Bool # | |||||
Data CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CaptionPosition -> c CaptionPosition # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CaptionPosition # toConstr :: CaptionPosition -> Constr # dataTypeOf :: CaptionPosition -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CaptionPosition) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CaptionPosition) # gmapT :: (forall b. Data b => b -> b) -> CaptionPosition -> CaptionPosition # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CaptionPosition -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CaptionPosition -> r # gmapQ :: (forall d. Data d => d -> u) -> CaptionPosition -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CaptionPosition -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CaptionPosition -> m CaptionPosition # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CaptionPosition -> m CaptionPosition # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CaptionPosition -> m CaptionPosition # | |||||
Generic CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Associated Types
Methods from :: CaptionPosition -> Rep CaptionPosition x # to :: Rep CaptionPosition x -> CaptionPosition # | |||||
Read CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods readsPrec :: Int -> ReadS CaptionPosition # readList :: ReadS [CaptionPosition] # | |||||
Show CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods showsPrec :: Int -> CaptionPosition -> ShowS # show :: CaptionPosition -> String # showList :: [CaptionPosition] -> ShowS # | |||||
Eq CaptionPosition Source # | |||||
Defined in Text.Pandoc.Options Methods (==) :: CaptionPosition -> CaptionPosition -> Bool # (/=) :: CaptionPosition -> CaptionPosition -> Bool # | |||||
type Rep CaptionPosition Source # | |||||