{- | Module : Referees.CLI.Args Copyright : (c) Pablo Couto 2014 License : GPL-3 Maintainer : pablo@infty.in Stability : experimental -} module Referees.CLI.Args where import Referees ( Language, fromCSVtoReferees, fromCSVtoProposals, distributeWith, profitRefProp, ppDistribution ) import Referees.Solver.Types ( Bounds, Capacity, mkBounds ) import Control.Applicative ( pure, (<$>), (<*>) ) import Control.Conditional ( whenM ) import Control.Exception ( assert ) import Control.Monad ( forM_, when ) import Data.Map ( Map ) import qualified Data.Map as Map ( fromList, insert, insertWith, lookup, singleton ) import Data.Version ( Version(..), showVersion ) import System.Console.CmdArgs.Explicit ( HelpFormat(HelpFormatOne), Mode, flagArg, flagHelpSimple, flagReq, helpText, mode ) import System.Console.CmdArgs.Text ( Text ) import System.Directory ( doesFileExist ) import System.Exit ( exitFailure ) import Text.Read ( readMaybe ) data Args = Args { _capacityArg :: Capacity , _boundsArg :: Bounds Int , _languageArg :: Maybe Language , _refereesArg :: FilePath , _proposalsArg :: FilePath } version :: Version version = Version { versionBranch = [0,0,0] , versionTags = [] } argsSpec :: Mode (Map String [String]) argsSpec = mode " referees" (Map.fromList [ ("capacity", ["1"]), ("min_copies", ["0"]) , ("max_copies", ["1"]), ("language", []) ]) "" (flagArg (add "file") " ") [ flagReq ["ca"] (upd "capacity") "" "Default capacity for referees with none assigned. \ \[default: 1]" , flagReq ["maxc"] (upd "max_copies") "" "Number of minimum copies per proposal to distribute. If this value \ \is higher than --maxc, or no --maxc is given, it will also be set as \ \the maximum number of copies to distribute. \ \[default: 0]" , flagReq ["minc"] (upd "min_copies") "" "Number of maximum copies per proposal to distribute. \ \[default: 1]" , flagReq ["l"] (upd "language") "" "Default language for referees with none assigned. \ \Providing a default language is optional." , flagHelpSimple (const $ Map.singleton "help" [""]) ] where upd flag val cmdargs = Right $ Map.insert flag [val] cmdargs add flag val cmdargs = Right $ Map.insertWith (flip (++)) flag [val] cmdargs help :: [Text] help = helpText [ "Referees v" ++ showVersion version ++ ", (c) Pablo Couto 2014" , "" , "This program comes with ABSOLUTELY NO WARRANTY.\n\ \This is free software, and you are welcome to redistribute it\n\ \under the terms and conditions of the GNU GPL v3 license \ \[https://www.gnu.org/copyleft/gpl.html]." , "" , "Example of use: " , "" , "$ referees \"referees.csv\" \"proposals.csv\" --ca=3 --minc=2 -l=English" , "" , "Usage options:" ] HelpFormatOne argsSpec -- | Performs the distribution according to the received arguments, pretty -- printing its result. -- runWithArgs :: Args -> IO () runWithArgs cmdargs = do dist <- distributeWith <$> pure profitRefProp <*> (fromCSVtoReferees $ _refereesArg cmdargs) <*> (pure $ _capacityArg cmdargs) <*> (pure $ _boundsArg cmdargs) <*> (pure $ _languageArg cmdargs) <*> (fromCSVtoProposals $ _proposalsArg cmdargs) putStrLn =<< ppDistribution <$> dist -- | Verifies that all arguments satisfy the relevant requirements, and fails -- the program if that is not the case. -- checkArgs :: Map String [String] -> IO Args checkArgs cmdargs = do let capacity' = readMaybe =<< fuse <$> Map.lookup "capacity" cmdargs :: Maybe Int minCopies' = readMaybe =<< fuse <$> Map.lookup "min_copies" cmdargs :: Maybe Int maxCopies' = readMaybe =<< fuse <$> Map.lookup "max_copies" cmdargs :: Maybe Int forM_ [capacity', maxCopies'] $ \ x -> maybe (putStrLn "Error: wrong type of argument(s) given." >> exitFailure) (const $ return ()) x let Just capacity = capacity' Just minCopies = minCopies' Just maxCopies = maxCopies' let Just bounds = if minCopies > maxCopies then mkBounds minCopies minCopies else mkBounds minCopies maxCopies let Just language = prepLangArg <$> Map.lookup "language" cmdargs let files = Map.lookup "file" cmdargs when ((length <$> files) /= Just 2) $ do putStrLn "Error: wrong number of arguments given." exitFailure let Just referees = (!! 0) <$> files Just proposals = (!! 1) <$> files forM_ [referees, proposals] $ \ x -> whenM (not <$> doesFileExist x) $ putStrLn ("Error: file “" ++ x ++ "” does not exist.") >> exitFailure return $ Args capacity bounds language referees proposals where prepLangArg s = case s of [] -> Nothing (s':_) -> Just s' fuse xs = assert (not . null $ xs) head xs