Safe Haskell | None |
---|---|
Language | Haskell98 |
some internal definitions. To use default persistence, import
Data.TCache.DefaultPersistence
instead
- type AccessTime = Integer
- type ModifTime = Integer
- data Status a
- = NotRead
- | DoNotExist
- | Exist a
- data Elem a = Elem !a !AccessTime !ModifTime
- type TPVar a = TVar (Status (Elem a))
- data DBRef a = DBRef !String !(TPVar a)
- castErr :: (Typeable * a, Typeable * t) => t -> a
- class Indexable a where
- class Serializable a where
- class PersistIndex a where
- type Key = String
- data Persist = Persist {}
- filePersist :: Persist
- defaultPersistIORef :: IORef Persist
- setDefaultPersist :: Persist -> IO ()
- getDefaultPersist :: Persist
- getPersist :: (Typeable * a, Serializable a) => a -> Persist
- defaultReadByKey :: String -> IO (Maybe ByteString)
- defaultWrite :: String -> ByteString -> IO ()
- safeWrite :: FilePath -> ByteString -> IO ()
- defaultDelete :: String -> IO ()
- defReadResourceByKey :: (Typeable * a, Indexable a, Serializable a) => [Char] -> IO (Maybe a)
- defWriteResource :: (Typeable * a, Serializable a, Indexable a) => a -> IO ()
- defDelResource :: (Serializable a, Typeable * a, Indexable a) => a -> IO ()
- readFileStrict :: FilePath -> IO ByteString
Documentation
type AccessTime = Integer Source #
class Indexable a where Source #
Indexable is an utility class used to derive instances of IResource
Example:
data Person= Person{ pname :: String, cars :: [DBRef Car]} deriving (Show, Read, Typeable) data Car= Car{owner :: DBRef Person , cname:: String} deriving (Show, Read, Eq, Typeable)
Since Person and Car are instances of Read
ans Show
, by defining the Indexable
instance
will implicitly define the IResource instance for file persistence:
instance Indexable Person where key Person{pname=n} = "Person " ++ n instance Indexable Car where key Car{cname= n} = "Car " ++ n
class Serializable a where Source #
Serialize is an alternative to the IResource class for defining persistence in TCache. The deserialization must be as lazy as possible. serialization/deserialization are not performance critical in TCache
Read, Show, instances are implicit instances of Serializable
serialize = pack . show deserialize= read . unpack
Since write and read to disk of to/from the cache are not be very frequent The performance of serialization is not critical.
serialize :: a -> ByteString Source #
deserialize :: ByteString -> a Source #
deserialKey :: String -> ByteString -> a Source #
setPersist :: a -> Maybe Persist Source #
class PersistIndex a where Source #
Used by IndexQuery for index persistence(see Data.TCache.IndexQuery.
persistIndex :: a -> Maybe Persist Source #
a persist mechanism has to implement these three primitives
filePersist
is the default file persistence
filePersist :: Persist Source #
Implements default default-persistence of objects in files with their keys as filenames
setDefaultPersist :: Persist -> IO () Source #
Set the default persistence mechanism of all serializable
objects that have
setPersist= const Nothing
. By default it is filePersist
this statement must be the first one before any other TCache call
getPersist :: (Typeable * a, Serializable a) => a -> Persist Source #
defaultReadByKey :: String -> IO (Maybe ByteString) Source #
defaultWrite :: String -> ByteString -> IO () Source #
defaultDelete :: String -> IO () Source #
defReadResourceByKey :: (Typeable * a, Indexable a, Serializable a) => [Char] -> IO (Maybe a) Source #
defWriteResource :: (Typeable * a, Serializable a, Indexable a) => a -> IO () Source #
defDelResource :: (Serializable a, Typeable * a, Indexable a) => a -> IO () Source #
readFileStrict :: FilePath -> IO ByteString Source #
Strict read from file, needed for default file persistence