module ImperativeState where import Data.Map import Control.Monad.State import Control.Monad.Error import UrlAnalyse import Control.Concurrent.MVar import Data.List data MyError = DownloadError String String | OtherError String | WikiUrlParseError String | NotImplementedError | NotExcatlyOneError String | NotIntegerError String | NotAtMostOneError String | ToManyOptionsError | PaperError instance Error MyError where noMsg = OtherError "A String Error!" strMsg s = OtherError s instance Show MyError where show (DownloadError theLemma theUrl) = "Error downloading the lemma \"" ++ theLemma ++ "\" form the url \"" ++ theUrl ++ "\"" show (WikiUrlParseError theUrl) = "Error: The supplied url " ++ theUrl ++ " could not be parsed" show NotImplementedError = "Error: The requested feature is not implemented yet" show PaperError = "Error: The option paper may only be one of A4,A5,B5,letter,legal,executive" show ToManyOptionsError = "Error: at most one of the options --internal --templates --message --html may be given" show (NotExcatlyOneError msg) = "Error: The option --" ++ msg ++ " has to be present exactly once in the command line" show (NotAtMostOneError msg) = "Error: The option --" ++ msg ++ " can only be present at most once in the command line" show (NotIntegerError msg) = "Error: The option --" ++ msg ++ " could not be parsed as an integer." show (OtherError msg) = msg data Contributor = Contributor{name :: String, edits :: Integer, href :: String} deriving (Eq, Ord, Show, Read) myplus :: Contributor -> Contributor -> Contributor myplus x y = x{edits = (edits x) + (edits y)} contribsum :: [Map String Contributor] -> Map String Contributor contribsum x = Data.List.foldl (unionWith myplus) Data.Map.empty x imperativeStateZero :: ImperativeState imperativeStateZero = ImperativeState{audict = [], fullUrl = fullWikiUrlZero, tmpPath = ""} data ImperativeState = ImperativeState{audict :: [MVar (Map String Contributor)], fullUrl :: FullWikiUrl, tmpPath :: String} type ImperativeMonad = ErrorT MyError (StateT ImperativeState IO) data RunMode = HTML | ExpandedTemplates | StandardTemplates | UserTemplateFile String deriving (Show, Read) data SourceMode = Included | Excluded deriving (Show, Read) data FullConfig = FullConfig{resolution :: Integer, outputFilename :: String, inputUrl :: String, runMode :: RunMode, paper :: String, vector :: Bool, copy :: Maybe String, mainPath :: String, server :: Maybe Int} deriving (Show, Read)