module QueueState
( QueueState ,
addMessage,
queueStep,
queueStart,
queueLength,
queueEmpty
) where
import Base
type Time = Int
data QueueState = QS Time Service [Inmess]
deriving (QueueState -> QueueState -> Bool
(QueueState -> QueueState -> Bool)
-> (QueueState -> QueueState -> Bool) -> Eq QueueState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueueState -> QueueState -> Bool
== :: QueueState -> QueueState -> Bool
$c/= :: QueueState -> QueueState -> Bool
/= :: QueueState -> QueueState -> Bool
Eq, Service -> QueueState -> ShowS
[QueueState] -> ShowS
QueueState -> String
(Service -> QueueState -> ShowS)
-> (QueueState -> String)
-> ([QueueState] -> ShowS)
-> Show QueueState
forall a.
(Service -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Service -> QueueState -> ShowS
showsPrec :: Service -> QueueState -> ShowS
$cshow :: QueueState -> String
show :: QueueState -> String
$cshowList :: [QueueState] -> ShowS
showList :: [QueueState] -> ShowS
Show)
addMessage :: Inmess -> QueueState -> QueueState
addMessage :: Inmess -> QueueState -> QueueState
addMessage Inmess
im (QS Service
time Service
serv [Inmess]
ml)
| Inmess -> Bool
isYes Inmess
im = Service -> Service -> [Inmess] -> QueueState
QS Service
time Service
serv ([Inmess]
ml[Inmess] -> [Inmess] -> [Inmess]
forall a. [a] -> [a] -> [a]
++[Inmess
im])
| Bool
otherwise = Service -> Service -> [Inmess] -> QueueState
QS Service
time Service
serv [Inmess]
ml
where
isYes :: Inmess -> Bool
isYes (Yes Service
_ Service
_) = Bool
True
isYes Inmess
_ = Bool
False
queueStep :: QueueState -> ( QueueState , [Outmess] )
queueStep :: QueueState -> (QueueState, [Outmess])
queueStep (QS Service
time Service
servSoFar (Yes Service
arr Service
serv : [Inmess]
inRest))
| Service
servSoFar Service -> Service -> Bool
forall a. Ord a => a -> a -> Bool
< Service
serv
= (Service -> Service -> [Inmess] -> QueueState
QS (Service
timeService -> Service -> Service
forall a. Num a => a -> a -> a
+Service
1) (Service
servSoFarService -> Service -> Service
forall a. Num a => a -> a -> a
+Service
1) (Service -> Service -> Inmess
Yes Service
arr Service
serv Inmess -> [Inmess] -> [Inmess]
forall a. a -> [a] -> [a]
: [Inmess]
inRest) , [])
| Bool
otherwise
= (Service -> Service -> [Inmess] -> QueueState
QS (Service
timeService -> Service -> Service
forall a. Num a => a -> a -> a
+Service
1) Service
0 [Inmess]
inRest , [Service -> Service -> Service -> Outmess
Discharge Service
arr (Service
timeService -> Service -> Service
forall a. Num a => a -> a -> a
-Service
servService -> Service -> Service
forall a. Num a => a -> a -> a
-Service
arr) Service
serv])
queueStep (QS Service
time Service
serv []) = (Service -> Service -> [Inmess] -> QueueState
QS (Service
timeService -> Service -> Service
forall a. Num a => a -> a -> a
+Service
1) Service
serv [] , [])
queueStart :: QueueState
queueStart :: QueueState
queueStart = Service -> Service -> [Inmess] -> QueueState
QS Service
0 Service
0 []
queueLength :: QueueState -> Int
queueLength :: QueueState -> Service
queueLength (QS Service
_ Service
_ [Inmess]
q) = [Inmess] -> Service
forall a. [a] -> Service
forall (t :: * -> *) a. Foldable t => t a -> Service
length [Inmess]
q
queueEmpty :: QueueState -> Bool
queueEmpty :: QueueState -> Bool
queueEmpty (QS Service
_ Service
_ [Inmess]
q) = ([Inmess]
q[Inmess] -> [Inmess] -> Bool
forall a. Eq a => a -> a -> Bool
==[])