{-# LANGUAGE TypeFamilies, FlexibleContexts, ConstrainedClassMethods #-}
module ALife.Creatur.Database
(
Database(..),
Record(..),
SizedRecord(..)
) where
import Prelude hiding (lookup)
import Control.Monad.State (StateT)
import Data.Serialize (Serialize)
class Record r where
key :: r -> String
class (Record r) => SizedRecord r where
size :: r -> Int
class Database d where
type DBRecord d
keys :: StateT d IO [String]
numRecords :: StateT d IO Int
archivedKeys :: StateT d IO [String]
lookup :: Serialize (DBRecord d) =>
String -> StateT d IO (Either String (DBRecord d))
lookupInArchive :: Serialize (DBRecord d) =>
String -> StateT d IO (Either String (DBRecord d))
readAll :: Serialize (DBRecord d) =>
StateT d IO [Either String (DBRecord d)]
readAll = StateT d IO [String]
forall d. Database d => StateT d IO [String]
keys StateT d IO [String]
-> ([String] -> StateT d IO [Either String (DBRecord d)])
-> StateT d IO [Either String (DBRecord d)]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> StateT d IO (Either String (DBRecord d)))
-> [String] -> StateT d IO [Either String (DBRecord d)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> StateT d IO (Either String (DBRecord d))
forall d.
(Database d, Serialize (DBRecord d)) =>
String -> StateT d IO (Either String (DBRecord d))
lookup
readAllInArchive :: Serialize (DBRecord d) =>
StateT d IO [Either String (DBRecord d)]
readAllInArchive = StateT d IO [String]
forall d. Database d => StateT d IO [String]
archivedKeys StateT d IO [String]
-> ([String] -> StateT d IO [Either String (DBRecord d)])
-> StateT d IO [Either String (DBRecord d)]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> StateT d IO (Either String (DBRecord d)))
-> [String] -> StateT d IO [Either String (DBRecord d)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> StateT d IO (Either String (DBRecord d))
forall d.
(Database d, Serialize (DBRecord d)) =>
String -> StateT d IO (Either String (DBRecord d))
lookupInArchive
store :: (Record (DBRecord d), Serialize (DBRecord d)) =>
DBRecord d -> StateT d IO ()
delete :: Serialize (DBRecord d) => String -> StateT d IO ()