module Text.Pandoc.Writers.LaTeX.Types
  ( LW
  , WriterState (..)
  , startingState
  ) where

import Control.Monad.State.Strict (StateT)
import Data.Text (Text)
import Text.DocLayout (Doc)
import Text.Pandoc.Options
  ( WriterOptions (writerIncremental, writerTopLevelDivision)
  , TopLevelDivision (..)
  )

-- | LaTeX writer type. The type constructor @m@ will typically be an
-- instance of PandocMonad.
type LW m = StateT WriterState m

data WriterState =
  WriterState
  { WriterState -> Bool
stInNote        :: Bool          -- ^ true if we're in a note
  , WriterState -> Bool
stInQuote       :: Bool          -- ^ true if in a blockquote
  , WriterState -> Bool
stExternalNotes :: Bool          -- ^ true if in context where
                                     --   we need to store footnotes
  , WriterState -> Bool
stInMinipage    :: Bool          -- ^ true if in minipage
  , WriterState -> Bool
stInHeading     :: Bool          -- ^ true if in a section heading
  , WriterState -> Bool
stInItem        :: Bool          -- ^ true if in \item[..]
  , WriterState -> [Doc Text]
stNotes         :: [Doc Text]    -- ^ notes in a minipage
  , WriterState -> Int
stOLLevel       :: Int           -- ^ level of ordered list nesting
  , WriterState -> WriterOptions
stOptions       :: WriterOptions -- ^ writer options, so they don't have to
                                     --   be parameter
  , WriterState -> Bool
stVerbInNote    :: Bool          -- ^ true if document has verbatim text in note
  , WriterState -> Bool
stTable         :: Bool          -- ^ true if document has a table
  , WriterState -> Bool
stMultiRow      :: Bool          -- ^ true if document has multirow cells
  , WriterState -> Bool
stStrikeout     :: Bool          -- ^ true if document has strikeout
  , WriterState -> Bool
stUrl           :: Bool          -- ^ true if document has visible URL link
  , WriterState -> Bool
stGraphics      :: Bool          -- ^ true if document contains images
  , WriterState -> Bool
stLHS           :: Bool          -- ^ true if document has literate haskell code
  , WriterState -> Bool
stHasChapters   :: Bool          -- ^ true if document has chapters
  , WriterState -> Bool
stCsquotes      :: Bool          -- ^ true if document uses csquotes
  , WriterState -> Bool
stHighlighting  :: Bool          -- ^ true if document has highlighted code
  , WriterState -> Bool
stIncremental   :: Bool          -- ^ true if beamer lists should be
                                     --   displayed bit by bit
  , WriterState -> [Text]
stInternalLinks :: [Text]        -- ^ list of internal link targets
  , WriterState -> Bool
stBeamer        :: Bool          -- ^ produce beamer
  , WriterState -> Bool
stEmptyLine     :: Bool          -- ^ true if no content on line
  , WriterState -> Bool
stHasCslRefs    :: Bool          -- ^ has a Div with class refs
  , WriterState -> Bool
stIsFirstInDefinition :: Bool    -- ^ first block in a defn list
  }

startingState :: WriterOptions -> WriterState
startingState :: WriterOptions -> WriterState
startingState WriterOptions
options =
  WriterState :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> [Doc Text]
-> Int
-> WriterOptions
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> WriterState
WriterState
  { stInNote :: Bool
stInNote = Bool
False
  , stInQuote :: Bool
stInQuote = Bool
False
  , stExternalNotes :: Bool
stExternalNotes = Bool
False
  , stInHeading :: Bool
stInHeading = Bool
False
  , stInMinipage :: Bool
stInMinipage = Bool
False
  , stInItem :: Bool
stInItem = Bool
False
  , stNotes :: [Doc Text]
stNotes = []
  , stOLLevel :: Int
stOLLevel = Int
1
  , stOptions :: WriterOptions
stOptions = WriterOptions
options
  , stVerbInNote :: Bool
stVerbInNote = Bool
False
  , stTable :: Bool
stTable = Bool
False
  , stMultiRow :: Bool
stMultiRow = Bool
False
  , stStrikeout :: Bool
stStrikeout = Bool
False
  , stUrl :: Bool
stUrl = Bool
False
  , stGraphics :: Bool
stGraphics = Bool
False
  , stLHS :: Bool
stLHS = Bool
False
  , stHasChapters :: Bool
stHasChapters = case WriterOptions -> TopLevelDivision
writerTopLevelDivision WriterOptions
options of
                      TopLevelDivision
TopLevelPart    -> Bool
True
                      TopLevelDivision
TopLevelChapter -> Bool
True
                      TopLevelDivision
_               -> Bool
False
  , stCsquotes :: Bool
stCsquotes = Bool
False
  , stHighlighting :: Bool
stHighlighting = Bool
False
  , stIncremental :: Bool
stIncremental = WriterOptions -> Bool
writerIncremental WriterOptions
options
  , stInternalLinks :: [Text]
stInternalLinks = []
  , stBeamer :: Bool
stBeamer = Bool
False
  , stEmptyLine :: Bool
stEmptyLine = Bool
True
  , stHasCslRefs :: Bool
stHasCslRefs = Bool
False
  , stIsFirstInDefinition :: Bool
stIsFirstInDefinition = Bool
False
  }