module Main (main) where import Control.Applicative import Control.Monad import Main.ParserCSV import Data.List import Ideas.Common.Id import Data.Monoid import Data.Maybe import Main.Report import qualified Main.Diagnose as D import Options.Applicative import Options.Applicative.Types import Recognize.Data.MathStoryProblem import Main.Tasks import Service.AdviseMe import System.Environment import Util.String data InputSource = File String | Stdin deriving (Show,Eq) string :: String -> ReadM () string s = readerAsk >>= \e -> guard (strToLower e == s) pExercise :: Parser Task pExercise = argument (foldl1 (<|>) [ t <$ string (showId t) | t <- tasks ]) argFields where argFields :: Mod ArgumentFields Task argFields = help ("Select an exercise: " ++ intercalate ", " (map showId tasks)) <> metavar "EXERCISE" pInputSource :: MathStoryProblem -> Parser InputSource pInputSource e = pInput (fromMaybe "input/default.csv" (inputFile e)) where pInput d = File <$> option str (long "file" <> short 'f' <> value d) <|> flag' Stdin (long "stdin" <> short 's') pDatabase :: Parser FilePath pDatabase = strArgument argFields where argFields :: Mod ArgumentFields FilePath argFields = help "Provide a database path." <> metavar "DATABASE" pExerciseOptions :: Parser (IO ()) pExerciseOptions = fromM $ do Task x <- oneM pExercise source <- oneM (pInputSource x) return $ print source >> case source of File s -> if isCSV s then readFileCSV s >>= D.diagnoseMultiple x >>= print else readFile s >>= D.diagnoseSingle x >>= print Stdin -> getContents >>= (\c -> length c `seq` D.diagnoseSingle x c >>= print) where isCSV = isSuffixOf "csv" pReportOptions :: Parser (IO ()) pReportOptions = fromM $ do s <- oneM pDatabase return $ reportDatabase s "report.html" pAll :: Parser (IO ()) pAll = pure $ forM_ tasks $ \(Task x) -> case inputFile x of Just s -> putStrLn ("Exercise:" ++ show x) >> readFileCSV s >>= D.diagnoseMultiple x >>= putStr . indent . show _ -> putStrLn ("No default CSV for: " ++ show x) commands :: Parser (IO ()) commands = hsubparser $ command "run" (info pExerciseOptions fullDesc) <> command "report" (info pReportOptions fullDesc) <> command "all" (info pAll fullDesc) <> command "help" (info (pure (do putStrLn "Use one of the following commands:" putStrLn "'run [exercise] [input]': Runs the given exercise from input/[exercise].csv, or from a different inputfile given in [input]." putStrLn "([input] can be '-f[filepath]' for file input or '-s' for standard input.)" putStrLn "'all': Runs every exercise from input/[exercise].csv." putStrLn "'report [filepath]': Generates a report on the database given in the filepath to out.html." putStrLn "" putStrLn "Use '--' to access the advise-me service. Examples:" putStrLn "'-- --file=[filepath]': Treats the file given as an xml input request and returns output response to screen." putStrLn "'-- --rerun=[filepath]': Treats the file given as a database and reruns all requests within it.")) fullDesc) <> help "one of: run, report, all, help" main :: IO () main = do args <- getArgs let (xs,ys) = unwords args `splitOn` "-- " xs' = breaksOn (== ' ') xs ys' = breaksOn (== ' ') ys if null xs then withArgs ys' runService else withArgs xs' $ join $ customExecParser (ParserPrefs "" False True True True 80) (info commands fullDesc)