Implement scheduling and make it the default mode
This commit is contained in:
parent
b21cd8d909
commit
2d9cfd818d
9 changed files with 180 additions and 54 deletions
|
@ -22,7 +22,9 @@ executable pilu
|
||||||
, Event
|
, Event
|
||||||
, Medicine
|
, Medicine
|
||||||
, Paths_pilu
|
, Paths_pilu
|
||||||
|
, Schedule
|
||||||
, Timeline
|
, Timeline
|
||||||
|
, YAML
|
||||||
-- other-extensions:
|
-- other-extensions:
|
||||||
build-depends: base >=4.9 && <4.13
|
build-depends: base >=4.9 && <4.13
|
||||||
, containers
|
, containers
|
||||||
|
@ -30,5 +32,6 @@ executable pilu
|
||||||
, optparse-applicative
|
, optparse-applicative
|
||||||
, parsec
|
, parsec
|
||||||
, time
|
, time
|
||||||
|
ghc-options: -Wall -dynamic
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
|
@ -4,7 +4,7 @@ module CLI (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Options.Applicative (
|
import Options.Applicative (
|
||||||
Parser, execParser, flag, flag', fullDesc, header, help, helper, info, long
|
Parser, execParser, flag, flag', fullDesc, header, help, helper, info, long, short
|
||||||
)
|
)
|
||||||
import Control.Applicative ((<**>), (<|>))
|
import Control.Applicative ((<**>), (<|>))
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
|
@ -18,9 +18,9 @@ versionStr = showVersion Pilu.version
|
||||||
|
|
||||||
invocation :: Parser Invocation
|
invocation :: Parser Invocation
|
||||||
invocation =
|
invocation =
|
||||||
flag' Schedule
|
flag' Inventory
|
||||||
(long "schedule" <> help "Show when next to go for provisioning")
|
(short 'i' <> long "inventory" <> help "Show a full inventory")
|
||||||
<|> flag Inventory (Version versionStr)
|
<|> flag Schedule (Version versionStr)
|
||||||
(long "version" <> help "Show the version number")
|
(long "version" <> help "Show the version number")
|
||||||
|
|
||||||
invoked :: IO Invocation
|
invoked :: IO Invocation
|
||||||
|
|
|
@ -32,11 +32,11 @@ quoted = char '"' *> many quotedChar <* char '"' <?> "quote ending the cell"
|
||||||
|
|
||||||
parse :: Row a => String -> Char -> String -> Either ParseError [a]
|
parse :: Row a => String -> Char -> String -> Either ParseError [a]
|
||||||
parse name separator input = do
|
parse name separator input = do
|
||||||
lines <- Parsec.parse (csvFile separator) name input
|
rows <- Parsec.parse (csvFile separator) name input
|
||||||
case lines of
|
case rows of
|
||||||
[] -> Right []
|
[] -> Right []
|
||||||
(header:rows) ->
|
(header:contents) ->
|
||||||
let assocs = Map.fromList . zipWith (,) header <$> rows in
|
let assocs = Map.fromList . zipWith (,) header <$> contents in
|
||||||
sequence $ zipWith parseRow [1..] assocs
|
sequence $ zipWith parseRow [1..] assocs
|
||||||
where
|
where
|
||||||
parseRow n row = either (errorAt n) return $ fromRow row
|
parseRow n row = either (errorAt n) return $ fromRow row
|
||||||
|
|
|
@ -5,7 +5,7 @@ module Event (
|
||||||
|
|
||||||
import CSV (Row(..))
|
import CSV (Row(..))
|
||||||
import Control.Monad (foldM)
|
import Control.Monad (foldM)
|
||||||
import Data.List (isSuffixOf, takeWhile, sortOn)
|
import Data.List (isSuffixOf, takeWhile)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import qualified Data.Map as Map (delete, empty, insert, lookup, toList)
|
import qualified Data.Map as Map (delete, empty, insert, lookup, toList)
|
||||||
import Data.Time (Day)
|
import Data.Time (Day)
|
||||||
|
@ -22,11 +22,11 @@ data Event = Event {
|
||||||
|
|
||||||
instance Row Event where
|
instance Row Event where
|
||||||
fromRow assoc = do
|
fromRow assoc = do
|
||||||
date <- read <$> get "date"
|
rowDate <- read <$> get "date"
|
||||||
(kind, ints) <- foldM addAmount (Nothing, Map.empty) . Map.toList $ Map.delete "date" assoc
|
(kind, ints) <- foldM addAmount (Nothing, Map.empty) . Map.toList $ Map.delete "date" assoc
|
||||||
maybe
|
maybe
|
||||||
(Left $ Expect "A prescription or provisioning for a medicine")
|
(Left $ Expect "A prescription or provisioning for a medicine")
|
||||||
(Right . Event date ints)
|
(Right . Event rowDate ints)
|
||||||
kind
|
kind
|
||||||
where
|
where
|
||||||
get key = maybe (Left $ Expect key) Right $ Map.lookup key assoc
|
get key = maybe (Left $ Expect key) Right $ Map.lookup key assoc
|
||||||
|
|
25
src/Main.hs
25
src/Main.hs
|
@ -1,12 +1,14 @@
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import CLI (Invocation(..), invoked)
|
import CLI (Invocation(..), invoked)
|
||||||
import CSV (Row, parse)
|
import CSV (Row, parse)
|
||||||
import Data.Time (UTCTime(..), getCurrentTime)
|
import Data.Time (UTCTime(..), getCurrentTime)
|
||||||
import Event (Event)
|
import Medicine (Pharmacy, pharmacy)
|
||||||
import Medicine (Medicine, Pharmacy, pharmacy)
|
|
||||||
import System.Exit (exitFailure, exitSuccess)
|
import System.Exit (exitFailure, exitSuccess)
|
||||||
import Timeline (State, currentState)
|
import Schedule (schedule)
|
||||||
|
import Timeline (State(..), stateAt)
|
||||||
|
import YAML (encode)
|
||||||
|
|
||||||
readCSV :: Row a => FilePath -> IO [a]
|
readCSV :: Row a => FilePath -> IO [a]
|
||||||
readCSV filePath = do
|
readCSV filePath = do
|
||||||
|
@ -15,17 +17,20 @@ readCSV filePath = do
|
||||||
Left e -> (putStrLn $ show e) >> exitFailure
|
Left e -> (putStrLn $ show e) >> exitFailure
|
||||||
Right rows -> return rows
|
Right rows -> return rows
|
||||||
|
|
||||||
getCurrentState :: IO State
|
getState :: Pharmacy -> IO State
|
||||||
getCurrentState =
|
getState aPharmacy =
|
||||||
currentState
|
stateAt
|
||||||
<$> (utctDay <$> getCurrentTime)
|
<$> (utctDay <$> getCurrentTime)
|
||||||
<*> (pharmacy <$> readCSV "medicine.csv")
|
<*> (return aPharmacy)
|
||||||
<*> readCSV "timeline.csv"
|
<*> readCSV "timeline.csv"
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
invocation <- invoked
|
invocation <- invoked
|
||||||
case invocation of
|
display <- case invocation of
|
||||||
Inventory -> show <$> getCurrentState >>= putStrLn
|
Inventory -> return $ const encode
|
||||||
Schedule -> putStrLn "schedule"
|
Schedule -> return $ \ph -> encode . schedule ph
|
||||||
Version version -> putStrLn version >> exitSuccess
|
Version version -> putStrLn version >> exitSuccess
|
||||||
|
thePharmacy <- pharmacy <$> readCSV "medicine.csv"
|
||||||
|
theState <- getState thePharmacy
|
||||||
|
putStrLn $ display thePharmacy theState
|
||||||
|
|
|
@ -3,7 +3,6 @@ module Medicine (
|
||||||
Medicine(..)
|
Medicine(..)
|
||||||
, MedicineName
|
, MedicineName
|
||||||
, Pharmacy
|
, Pharmacy
|
||||||
, Stock
|
|
||||||
, pharmacy
|
, pharmacy
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -16,18 +15,19 @@ type MedicineName = String
|
||||||
|
|
||||||
data Medicine = Medicine {
|
data Medicine = Medicine {
|
||||||
name :: MedicineName
|
name :: MedicineName
|
||||||
|
, content :: Float
|
||||||
, minStock :: Float
|
, minStock :: Float
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
instance Row Medicine where
|
instance Row Medicine where
|
||||||
fromRow assoc = Medicine <$>
|
fromRow assoc = Medicine <$>
|
||||||
get "name"
|
get "name"
|
||||||
|
<*> (read <$> get "content")
|
||||||
<*> (read <$> get "minStock")
|
<*> (read <$> get "minStock")
|
||||||
where
|
where
|
||||||
get key = maybe (Left $ Expect key) Right $ Map.lookup key assoc
|
get key = maybe (Left $ Expect key) Right $ Map.lookup key assoc
|
||||||
|
|
||||||
type Pharmacy = Map MedicineName Medicine
|
type Pharmacy = Map MedicineName Medicine
|
||||||
type Stock = Map MedicineName Float
|
|
||||||
|
|
||||||
pharmacy :: [Medicine] -> Pharmacy
|
pharmacy :: [Medicine] -> Pharmacy
|
||||||
pharmacy = foldr (\medicine -> Map.insert (name medicine) medicine) Map.empty
|
pharmacy = foldr (\medicine -> Map.insert (name medicine) medicine) Map.empty
|
||||||
|
|
80
src/Schedule.hs
Normal file
80
src/Schedule.hs
Normal file
|
@ -0,0 +1,80 @@
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
module Schedule (
|
||||||
|
schedule
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Map ((!), Map, elems, lookupMin, mapWithKey, partition, size)
|
||||||
|
import qualified Data.Map as Map (filter)
|
||||||
|
import Data.Time (Day, addDays)
|
||||||
|
import Medicine (Medicine(..), MedicineName, Pharmacy)
|
||||||
|
import Timeline (State(..))
|
||||||
|
import YAML ((.:), Value(..), YAML(..))
|
||||||
|
|
||||||
|
data ScheduleType = NextBox | Provision | OutOfStock deriving (Eq, Show)
|
||||||
|
|
||||||
|
instance YAML ScheduleType where
|
||||||
|
toYAML NextBox = Simple "start a new box"
|
||||||
|
toYAML Provision = Simple "go to the pharmacy get some more"
|
||||||
|
toYAML OutOfStock = Simple "out of it"
|
||||||
|
|
||||||
|
data Schedule = Schedule {
|
||||||
|
days :: Integer
|
||||||
|
, date :: Day
|
||||||
|
, scheduleType :: ScheduleType
|
||||||
|
} deriving (Show)
|
||||||
|
|
||||||
|
instance YAML (Map MedicineName Schedule) where
|
||||||
|
toYAML schedules = Object $ outOfStocks ++ nextDay
|
||||||
|
where
|
||||||
|
(urgent, normal) = partition ((== OutOfStock) . scheduleType) schedules
|
||||||
|
outOfStocks =
|
||||||
|
if size urgent > 0
|
||||||
|
then ["Warning ! Out of" .: (Object . timing <$> urgent)]
|
||||||
|
else []
|
||||||
|
nextDay = maybe [] (scheduleNext normal) (snd <$> lookupMin normal)
|
||||||
|
|
||||||
|
scheduleNext :: Map MedicineName Schedule -> Schedule -> [(String, Value)]
|
||||||
|
scheduleNext schedules aSchedule = ["Schedule" .: (Object $
|
||||||
|
timing aSchedule
|
||||||
|
++ ["TODO" .: (scheduleType <$> schedules)]
|
||||||
|
)]
|
||||||
|
|
||||||
|
timing :: Schedule -> [(String, Value)]
|
||||||
|
timing aSchedule =
|
||||||
|
["On" .: date aSchedule, "In" .: (show (days aSchedule) ++ " days")]
|
||||||
|
|
||||||
|
zipWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
|
||||||
|
zipWithKey f as bs =
|
||||||
|
mapWithKey (\k -> f k $ as ! k) bs
|
||||||
|
|
||||||
|
scheduleByMedicine :: Pharmacy -> Day -> MedicineName -> Float -> Float -> Schedule
|
||||||
|
scheduleByMedicine pharmacy day medicineName stockLeft rate =
|
||||||
|
let (scheduleType, amount) = typeAndAmount stockLeft minStock leftInBox in
|
||||||
|
let days = truncate (amount / rate) in
|
||||||
|
Schedule {days, date = days `addDays` day, scheduleType}
|
||||||
|
where
|
||||||
|
(Medicine {minStock, content}) = pharmacy ! medicineName
|
||||||
|
truncateF = fromInteger . truncate
|
||||||
|
leftInBox = content - (truncateF (content / stockLeft) * stockLeft)
|
||||||
|
|
||||||
|
typeAndAmount :: Float -> Float -> Float -> (ScheduleType, Float)
|
||||||
|
typeAndAmount stockLeft minStock leftInBox =
|
||||||
|
if secureLeft > 0
|
||||||
|
then
|
||||||
|
if secureLeft < leftInBox
|
||||||
|
then (Provision, secureLeft)
|
||||||
|
else (NextBox, leftInBox)
|
||||||
|
else (OutOfStock, stockLeft)
|
||||||
|
where
|
||||||
|
secureLeft = stockLeft - minStock
|
||||||
|
|
||||||
|
schedule :: Pharmacy -> State -> Map MedicineName Schedule
|
||||||
|
schedule pharmacy (State {day, stock, consumptionRate}) =
|
||||||
|
Map.filter keep schedules
|
||||||
|
where
|
||||||
|
schedules =
|
||||||
|
zipWithKey (scheduleByMedicine pharmacy day) stock consumptionRate
|
||||||
|
minDays = minimum . elems $ days <$> schedules
|
||||||
|
keep aSchedule =
|
||||||
|
days aSchedule == minDays || scheduleType aSchedule == OutOfStock
|
|
@ -1,40 +1,31 @@
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
module Timeline (
|
module Timeline (
|
||||||
State
|
State(..)
|
||||||
, currentState
|
, stateAt
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad (foldM, join)
|
|
||||||
import Control.Monad.Reader (Reader, runReader, ask)
|
|
||||||
import Data.List (sortOn)
|
import Data.List (sortOn)
|
||||||
import Data.Map ((!), Map, mapWithKey, toList)
|
import Data.Map ((!), Map, mapWithKey)
|
||||||
import Data.Time (Day, diffDays)
|
import Data.Time (Day, diffDays)
|
||||||
import Event (Event(..), EventType(..))
|
import Event (Event(..), EventType(..))
|
||||||
import Medicine (Pharmacy, Stock)
|
import Medicine (MedicineName, Pharmacy)
|
||||||
|
import YAML ((.:), Value(..), YAML(..))
|
||||||
type ConsumptionRate = Map String Float
|
|
||||||
|
|
||||||
data State = State {
|
data State = State {
|
||||||
day :: Day
|
day :: Day
|
||||||
, stock :: Stock
|
, stock :: Map MedicineName Float
|
||||||
, consumptionRate :: ConsumptionRate
|
, consumptionRate :: Map String Float
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Show State where
|
instance YAML State where
|
||||||
show (State {day, stock, consumptionRate}) = unlines $
|
toYAML (State {day, stock, consumptionRate}) = Object [
|
||||||
("day: " ++ show day)
|
"date" .: day
|
||||||
: ("stock:" : (indent <$> showAssoc stock) :: [String])
|
, "stock" .: stock
|
||||||
++ ("consumptionRate:" : (indent <$> showAssoc consumptionRate))
|
, "consumption rates" .: consumptionRate
|
||||||
where
|
]
|
||||||
indent :: String -> String
|
|
||||||
indent = ('\t' :)
|
|
||||||
showAssoc :: Show a => Map String a -> [String]
|
|
||||||
showAssoc = fmap (\(key, val) -> key ++ ": " ++ show val) . toList
|
|
||||||
|
|
||||||
initState :: Reader Pharmacy State
|
initState :: Pharmacy -> State
|
||||||
initState = do
|
initState pharmacy = State {
|
||||||
pharmacy <- ask
|
|
||||||
return $ State {
|
|
||||||
day = toEnum 0
|
day = toEnum 0
|
||||||
, stock = const 0 <$> pharmacy
|
, stock = const 0 <$> pharmacy
|
||||||
, consumptionRate = const 0 <$> pharmacy
|
, consumptionRate = const 0 <$> pharmacy
|
||||||
|
@ -59,10 +50,8 @@ setDay newDay state@(State {day, stock, consumptionRate}) = state {
|
||||||
consume medicineName initialAmount =
|
consume medicineName initialAmount =
|
||||||
max 0 $ initialAmount - duration * (consumptionRate ! medicineName)
|
max 0 $ initialAmount - duration * (consumptionRate ! medicineName)
|
||||||
|
|
||||||
lastState :: [Event] -> Reader Pharmacy State
|
stateAt :: Day -> Pharmacy -> [Event] -> State
|
||||||
lastState events =
|
stateAt targetDay pharmacy events =
|
||||||
foldl applyEvent <$> initState <*> (return $ sortOn date events)
|
setDay targetDay lastState
|
||||||
|
where
|
||||||
currentState :: Day -> Pharmacy -> [Event] -> State
|
lastState = foldl applyEvent (initState pharmacy) (sortOn date events)
|
||||||
currentState targetDay pharmacy events =
|
|
||||||
setDay targetDay (runReader (lastState events) pharmacy)
|
|
||||||
|
|
49
src/YAML.hs
Normal file
49
src/YAML.hs
Normal file
|
@ -0,0 +1,49 @@
|
||||||
|
{-# LANGUAGE TypeSynonymInstances #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
module YAML (
|
||||||
|
(.:)
|
||||||
|
, Value(..)
|
||||||
|
, YAML(..)
|
||||||
|
, encode
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.List (intercalate)
|
||||||
|
import Data.Map (Map, toList)
|
||||||
|
|
||||||
|
data Value = Simple String | Array [Value] | Object [(String, Value)] deriving (Show)
|
||||||
|
|
||||||
|
class YAML a where
|
||||||
|
toYAML :: a -> Value
|
||||||
|
|
||||||
|
instance YAML Value where
|
||||||
|
toYAML = id
|
||||||
|
|
||||||
|
instance {-# OVERLAPPABLE #-} YAML a => YAML [a] where
|
||||||
|
toYAML = Array . fmap toYAML
|
||||||
|
|
||||||
|
instance {-# OVERLAPPABLE #-} YAML a => YAML (Map String a) where
|
||||||
|
toYAML = Object . toList . fmap toYAML
|
||||||
|
|
||||||
|
instance {-# OVERLAPPABLE #-} Show a => YAML a where
|
||||||
|
toYAML = Simple . show
|
||||||
|
|
||||||
|
instance YAML String where
|
||||||
|
toYAML = Simple
|
||||||
|
|
||||||
|
encode :: YAML a => a -> String
|
||||||
|
encode = intercalate "\n" . getLines . toYAML
|
||||||
|
where
|
||||||
|
getLines (Simple s) = lines s
|
||||||
|
getLines (Array l) = concat $ (dashFirst . getLines) <$> l
|
||||||
|
getLines (Object m) = concat $ keyVal <$> m
|
||||||
|
dashFirst [] = []
|
||||||
|
dashFirst (l:ls) = ("- " ++ l) : ((" " ++) <$> ls)
|
||||||
|
keyVal (k, Simple s) =
|
||||||
|
case lines s of
|
||||||
|
[v] -> [k ++ ": " ++ v]
|
||||||
|
l -> (k ++ ": |") : (('\t' :) <$> l)
|
||||||
|
keyVal (k, v) = (k ++ ":") : (('\t' :) <$> getLines v)
|
||||||
|
|
||||||
|
(.:) :: YAML a => String -> a -> (String, Value)
|
||||||
|
(.:) k v = (k, toYAML v)
|
Loading…
Reference in a new issue