{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module ALife.Creatur.Counter
(
Counter(..),
PersistentCounter,
mkPersistentCounter
) where
import ALife.Creatur.Clock (Clock, currentTime, incTime)
import ALife.Creatur.Persistent (Persistent, mkPersistent, getPS, putPS)
import Control.Monad.State (StateT)
class Counter c where
current :: StateT c IO Int
increment :: StateT c IO ()
type PersistentCounter = Persistent Int
mkPersistentCounter :: FilePath -> PersistentCounter
mkPersistentCounter :: FilePath -> PersistentCounter
mkPersistentCounter = Int -> FilePath -> PersistentCounter
forall a. a -> FilePath -> Persistent a
mkPersistent Int
0
instance Counter PersistentCounter where
current :: StateT PersistentCounter IO Int
current = StateT PersistentCounter IO Int
forall a. Read a => StateT (Persistent a) IO a
getPS
increment :: StateT PersistentCounter IO ()
increment = do
Int
k <- StateT PersistentCounter IO Int
forall a. Read a => StateT (Persistent a) IO a
getPS
Int -> StateT PersistentCounter IO ()
forall a. (Show a, Read a) => a -> StateT (Persistent a) IO ()
putPS (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
instance Clock PersistentCounter where
currentTime :: StateT PersistentCounter IO Int
currentTime = StateT PersistentCounter IO Int
forall c. Counter c => StateT c IO Int
current
incTime :: StateT PersistentCounter IO ()
incTime = StateT PersistentCounter IO ()
forall c. Counter c => StateT c IO ()
increment