{-| A module for mutable states used in the programm -} module MyState where import qualified Data.Map as Map import Data.Map.Strict (Map) import Control.Monad.Trans.State (State) import MediaWikiParseTree import BaseFont {-| a type used as mutable state while processing a table. See documentation of the TableHelper module -} data TableState = TableState{rowCounter :: Int, inputLastRowOfHeader :: Int, outputLastRowOfHeader :: Int, outputTableHasHeaderRows :: Bool, lastRowHadEmptyMultiRowMap :: Bool, isFirstRow :: Bool, lastCellWasHeaderCell :: Bool, stillInTableHeader :: Bool, currentColumn :: Int, multiRowMap :: Map Int (Int, Int), numberOfColumnsInTable :: Int, lastCellWasMultiRow :: Bool, seperatingLinesRequestedForTable :: Bool, currentRowIsHeaderRow :: Bool, lastCellWasNotFirstCellOfRow :: Bool, columnsWidthList :: [Float], lastCellWasMultiColumn :: Bool, activeColumn :: Maybe Int} {-| see documentation of the makeLables function in WikiHelper module -} data UrlState = UrlState{iUrlState :: Int, sUrlState :: String, mUrlState :: Map String String} deriving (Show, Eq, Read) {-| see initial value of the type UrlState -} initialUrlState :: UrlState initialUrlState = UrlState{iUrlState = 0, sUrlState = "", mUrlState = Map.empty} {-| a type used as mutable state during the course of the LaTeXRederer -} data MyState = MyState{getImages :: [String], getJ :: Int, getF :: Float, getC :: Int, getInTab :: Int, getInGallery :: Bool, getInFootnote :: Bool, getInHeading :: Bool, getInCenter :: Bool, getInCode :: Bool, getTitle :: String, templateMap :: Map String [String], urls :: Map String String, urld :: WikiUrlData, getGalleryNumbers :: [Integer], currentUrl :: String, fndict :: Map String [Anything Char], tablist :: [[String]], tabmap :: Map Int (Map Int Double), fontStack :: [FontStyle], font :: Font, langu :: Maybe String, forms :: Map String Int, lastChar :: Char, lastFontChanged :: Bool} deriving (Show, Eq) {-| Renderer is the State monad using MyState as mutable state -} type Renderer = State MyState {-| the initial value for MyState -} initialState :: MyState initialState = MyState{getImages = [], getJ = 1, getF = 1, getC = 1, getInTab = 0, getInGallery = False, getInFootnote = False, getInHeading = False, getInCenter = False, getInCode = False, getTitle = "", templateMap = Map.fromList [], urls = Map.empty, urld = BaseUrl (WikiBaseUrl ""), getGalleryNumbers = [], currentUrl = "", fndict = Map.empty, tablist = [], tabmap = Map.empty, fontStack = [FontStyle{stylebase = Normal, bold = False, italic = False}], font = ComputerModernRoman, langu = Nothing, forms = Map.empty, lastChar = ' ', lastFontChanged = False} {-| represents an URL to a wiki (not to a page thereof), which is not a sister project of wikipedia, so not wikibooks wikisource, etc. -} data WikiBaseUrl = WikiBaseUrl{baseUrl :: String} deriving (Show, Eq) {-| represents an URL to a wiki (not to a page thereof), which is a sister project of wikipedia, so wikibooks wikisource, etc. -} data WikiUrlInfo = WikiUrlInfo{language :: String, wikitype :: String} deriving (Show, Eq) {-| represents an URL to a wiki (not to a page thereof), which is either a sister project of wikipedia, so wikibooks wikisource, etc. or isn't a sister project of wikipedia -} data WikiUrlData = BaseUrl WikiBaseUrl | UrlInfo WikiUrlInfo deriving (Show, Eq) {-| represents an URL to a page on a wiki -} data WikiLinkInfo = WikiLinkInfo{urldata :: WikiUrlData, page :: String} deriving (Show, Eq)