{-# LANGUAGE OverloadedStrings#-}
module Text.Pandoc.CrossRef.Util.Options (Options(..), isLatexFormat) where
import Data.Text (Text)
import Text.Pandoc.CrossRef.Util.Template
import Text.Pandoc.CrossRef.Util.Util (isFormat)
import Text.Pandoc.Definition
data Options = Options { Options -> Bool
cref :: Bool
, Options -> Int
chaptersDepth :: Int
, Options -> Bool
listings :: Bool
, Options -> Bool
codeBlockCaptions :: Bool
, Options -> Bool
autoSectionLabels :: Bool
, Options -> Bool
numberSections :: Bool
, Options -> Int
sectionsDepth :: Int
, Options -> Bool -> Int -> [Inline]
figPrefix :: Bool -> Int -> [Inline]
, Options -> Bool -> Int -> [Inline]
eqnPrefix :: Bool -> Int -> [Inline]
, Options -> Bool -> Int -> [Inline]
tblPrefix :: Bool -> Int -> [Inline]
, Options -> Bool -> Int -> [Inline]
lstPrefix :: Bool -> Int -> [Inline]
, Options -> Bool -> Int -> [Inline]
secPrefix :: Bool -> Int -> [Inline]
, Options -> Template
figPrefixTemplate :: Template
, Options -> Template
eqnPrefixTemplate :: Template
, Options -> Template
tblPrefixTemplate :: Template
, Options -> Template
lstPrefixTemplate :: Template
, Options -> Template
secPrefixTemplate :: Template
, Options -> BlockTemplate
lofItemTemplate :: BlockTemplate
, Options -> BlockTemplate
lotItemTemplate :: BlockTemplate
, Options -> BlockTemplate
lolItemTemplate :: BlockTemplate
, Options -> BlockTemplate
eqnBlockTemplate :: BlockTemplate
, Options -> Bool
eqnBlockInlineMath :: Bool
, Options -> Template
eqnIndexTemplate :: Template
, Options -> Template
eqnInlineTemplate :: Template
, Options -> Text -> Template
refIndexTemplate :: Text -> Template
, Options -> Template
subfigureRefIndexTemplate :: Template
, :: Template
, Options -> [Inline]
chapDelim :: [Inline]
, Options -> [Inline]
rangeDelim :: [Inline]
, Options -> [Inline]
pairDelim :: [Inline]
, Options -> [Inline]
lastDelim :: [Inline]
, Options -> [Inline]
refDelim :: [Inline]
, Options -> [Block]
lofTitle :: [Block]
, Options -> [Block]
lotTitle :: [Block]
, Options -> [Block]
lolTitle :: [Block]
, Options -> Maybe Format
outFormat :: Maybe Format
, Options -> Template
figureTemplate :: Template
, Options -> Template
subfigureTemplate :: Template
, Options -> Template
subfigureChildTemplate :: Template
, Options -> Template
ccsTemplate :: Template
, Options -> Template
tableTemplate :: Template
, Options -> Template
listingTemplate :: Template
, Options -> Text -> Int -> Maybe Text
customLabel :: Text -> Int -> Maybe Text
, Options -> Int -> Int -> Maybe Text
customHeadingLabel :: Int -> Int -> Maybe Text
, Options -> [Inline]
ccsDelim :: [Inline]
, Options -> [Inline]
ccsLabelSep :: [Inline]
, Options -> Bool
tableEqns :: Bool
, Options -> Bool
autoEqnLabels :: Bool
, Options -> Bool
subfigGrid :: Bool
, Options -> Bool
linkReferences :: Bool
, Options -> Bool
nameInLink :: Bool
, Options -> Bool
setLabelAttribute :: Bool
, Options -> Text
equationNumberTeX :: Text
}
isLatexFormat :: Options -> Bool
isLatexFormat :: Options -> Bool
isLatexFormat = (Bool -> Bool -> Bool
(||) (Bool -> Bool -> Bool)
-> (Maybe Format -> Bool) -> Maybe Format -> Bool -> Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Maybe Format -> Bool
isFormat Text
"latex") (Maybe Format -> Bool -> Bool)
-> (Maybe Format -> Bool) -> Maybe Format -> Bool
forall a b.
(Maybe Format -> a -> b)
-> (Maybe Format -> a) -> Maybe Format -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Maybe Format -> Bool
isFormat Text
"beamer")) (Maybe Format -> Bool)
-> (Options -> Maybe Format) -> Options -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe Format
outFormat