pilu/src/Main.hs

37 lines
1.0 KiB
Haskell

{-# LANGUAGE NamedFieldPuns #-}
module Main where
import CLI (Invocation(..), invoked)
import CSV (Row, parse)
import Data.Time (UTCTime(..), getCurrentTime)
import Medicine (Pharmacy, pharmacy)
import System.Exit (exitFailure, exitSuccess)
import Schedule (schedule)
import Timeline (State(..), stateAt)
import YAML (encode)
readCSV :: Row a => FilePath -> IO [a]
readCSV filePath = do
parsed <- parse filePath '\t' <$> readFile filePath
case parsed of
Left e -> (putStrLn $ show e) >> exitFailure
Right rows -> return rows
getState :: Pharmacy -> IO State
getState aPharmacy =
stateAt
<$> (utctDay <$> getCurrentTime)
<*> (return aPharmacy)
<*> readCSV "timeline.csv"
main :: IO ()
main = do
invocation <- invoked
display <- case invocation of
Inventory -> return $ const encode
Schedule -> return $ \ph -> encode . schedule ph
Version version -> putStrLn version >> exitSuccess
thePharmacy <- pharmacy <$> readCSV "medicine.csv"
theState <- getState thePharmacy
putStrLn $ display thePharmacy theState