pilu/src/Medicine.hs

32 lines
796 B
Haskell

{-# LANGUAGE NamedFieldPuns #-}
module Medicine (
Medicine(..)
, Pharmacy
, pharmacy
) where
import CSV (Row(..))
import Data.Map (Map)
import qualified Data.Map as Map (empty, insert, lookup)
import Text.ParserCombinators.Parsec.Error (Message(..))
data Medicine = Medicine {
name :: String
, content :: Int
, minStock :: Int
} deriving (Show)
instance Row Medicine where
fromRow assoc = Medicine <$>
get "name"
<*> (read <$> get "content")
<*> (read <$> get "minStock")
where
get key = maybe (Left $ Expect key) Right $ Map.lookup key assoc
type Pharmacy = Map String Medicine
pharmacy :: [Medicine] -> Pharmacy
pharmacy [] = Map.empty
pharmacy (medicine:medicines) = Map.insert (name medicine) medicine $ pharmacy medicines