pandoc-3.2: Conversion between markup formats
CopyrightCopyright (C) 2006-2024 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.Logging

Description

This module provides data types and functions for warnings and info messages.

Synopsis

Documentation

data Verbosity Source #

Verbosity level.

Constructors

ERROR 
WARNING 
INFO 

Instances

Instances details
FromJSON Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

ToJSON Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Data Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verbosity -> c Verbosity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Verbosity #

toConstr :: Verbosity -> Constr #

dataTypeOf :: Verbosity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Verbosity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity) #

gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Verbosity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Verbosity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

Bounded Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Enum Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Generic Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Associated Types

type Rep Verbosity :: Type -> Type #

Read Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Show Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Eq Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

Ord Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

type Rep Verbosity Source # 
Instance details

Defined in Text.Pandoc.Logging

type Rep Verbosity = D1 ('MetaData "Verbosity" "Text.Pandoc.Logging" "pandoc-3.2-9OxvYIIMDdN7XO18ZPRiBy" 'False) (C1 ('MetaCons "ERROR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WARNING" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "INFO" 'PrefixI 'False) (U1 :: Type -> Type)))

data LogMessage Source #

Constructors

SkippedContent Text SourcePos 
IgnoredElement Text 
DuplicateLinkReference Text SourcePos 
DuplicateNoteReference Text SourcePos 
NoteDefinedButNotUsed Text SourcePos 
DuplicateIdentifier Text SourcePos 
ReferenceNotFound Text SourcePos 
CircularReference Text SourcePos 
UndefinedToggle Text SourcePos 
ParsingUnescaped Text SourcePos 
CouldNotLoadIncludeFile Text SourcePos 
CouldNotParseIncludeFile Text SourcePos 
MacroAlreadyDefined Text SourcePos 
InlineNotRendered Inline 
BlockNotRendered Block 
DocxParserWarning Text 
PowerpointTemplateWarning Text 
IgnoredIOError Text 
CouldNotFetchResource Text Text 
CouldNotDetermineImageSize Text Text 
CouldNotConvertImage Text Text 
CouldNotDetermineMimeType Text 
CouldNotConvertTeXMath Text Text 
CouldNotParseCSS Text 
Fetching Text 
Extracting Text 
LoadedResource FilePath FilePath 
ScriptingInfo Text (Maybe SourcePos) 
ScriptingWarning Text (Maybe SourcePos) 
NoTitleElement Text 
NoLangSpecified 
InvalidLang Text 
CouldNotHighlight Text 
MissingCharacter Text 
Deprecated Text Text 
NoTranslation Text 
CouldNotLoadTranslations Text Text 
UnusualConversion Text 
UnexpectedXmlElement Text Text 
UnknownOrgExportOption Text 
CouldNotDeduceFormat [Text] Text 
RunningFilter FilePath 
FilterCompleted FilePath Integer 
CiteprocWarning Text 
ATXHeadingInLHS Int Text 
EnvironmentVariableUndefined Text 
DuplicateAttribute Text Text 
NotUTF8Encoded FilePath 
MakePDFInfo Text Text 
MakePDFWarning Text 
UnclosedDiv SourcePos SourcePos 
UnsupportedCodePage Int 

Instances

Instances details
ToJSON LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

Data LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogMessage -> c LogMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogMessage #

toConstr :: LogMessage -> Constr #

dataTypeOf :: LogMessage -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LogMessage) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogMessage) #

gmapT :: (forall b. Data b => b -> b) -> LogMessage -> LogMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogMessage -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> LogMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LogMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogMessage -> m LogMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogMessage -> m LogMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogMessage -> m LogMessage #

Generic LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

Associated Types

type Rep LogMessage :: Type -> Type #

Show LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

Eq LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

Ord LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

type Rep LogMessage Source # 
Instance details

Defined in Text.Pandoc.Logging

type Rep LogMessage = D1 ('MetaData "LogMessage" "Text.Pandoc.Logging" "pandoc-3.2-9OxvYIIMDdN7XO18ZPRiBy" 'False) (((((C1 ('MetaCons "SkippedContent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: (C1 ('MetaCons "IgnoredElement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "DuplicateLinkReference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)))) :+: (C1 ('MetaCons "DuplicateNoteReference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: (C1 ('MetaCons "NoteDefinedButNotUsed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: C1 ('MetaCons "DuplicateIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))) :+: ((C1 ('MetaCons "ReferenceNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: (C1 ('MetaCons "CircularReference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: C1 ('MetaCons "UndefinedToggle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)))) :+: ((C1 ('MetaCons "ParsingUnescaped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: C1 ('MetaCons "CouldNotLoadIncludeFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))) :+: (C1 ('MetaCons "CouldNotParseIncludeFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: C1 ('MetaCons "MacroAlreadyDefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)))))) :+: (((C1 ('MetaCons "InlineNotRendered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline)) :+: (C1 ('MetaCons "BlockNotRendered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: C1 ('MetaCons "DocxParserWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: (C1 ('MetaCons "PowerpointTemplateWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "IgnoredIOError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CouldNotFetchResource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) :+: ((C1 ('MetaCons "CouldNotDetermineImageSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "CouldNotConvertImage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CouldNotDetermineMimeType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "CouldNotConvertTeXMath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CouldNotParseCSS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "Fetching" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Extracting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))) :+: ((((C1 ('MetaCons "LoadedResource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: (C1 ('MetaCons "ScriptingInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SourcePos))) :+: C1 ('MetaCons "ScriptingWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SourcePos))))) :+: (C1 ('MetaCons "NoTitleElement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "NoLangSpecified" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidLang" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) :+: ((C1 ('MetaCons "CouldNotHighlight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "MissingCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Deprecated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "NoTranslation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CouldNotLoadTranslations" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "UnusualConversion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "UnexpectedXmlElement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))) :+: (((C1 ('MetaCons "UnknownOrgExportOption" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "CouldNotDeduceFormat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "RunningFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) :+: (C1 ('MetaCons "FilterCompleted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "CiteprocWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "ATXHeadingInLHS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) :+: ((C1 ('MetaCons "EnvironmentVariableUndefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "DuplicateAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "NotUTF8Encoded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) :+: ((C1 ('MetaCons "MakePDFInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "MakePDFWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "UnclosedDiv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)) :+: C1 ('MetaCons "UnsupportedCodePage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))))