Safe Haskell | None |
---|
- type SerializerContext l c = (MVar Cache, l, CountDest c)
- cSer :: (Multiset c, Allocator l) => Persister a -> SerializerContext l c -> (a -> Dest -> IO z) -> a -> Dest -> IO z
- serializeToArray :: AllocCopy w => Persister a -> a -> PrimArray Pinned w
- type Address = Len Word64 Word64
- cDeser :: Persister a -> DeserializerContext -> Deserializer Free a
- deserializeFromArray :: (Allocation f, Allocation df, Deserializable w) => Deserializer df a -> ArrayRange (PrimArray f w) -> DeserOut a
- deserializeFromFullArray :: forall f df w a. (Allocation f, Allocation df, Deserializable w, LgMultiple w Bool, Prim w) => Deserializer df a -> ArrayRange (PrimArray f w) -> a
- unsafeSeqDeserializer :: Persister a -> Deserializer Free a
- newtype Deserializer f a = Deserializer {}
- class Deserializable a where
- deserInput :: (Allocation f, Allocation f') => ArrayRange (PrimArray f a) -> ArrayRange (PrimArray f' Word)
- data DeserOut a = DeserOut {
- deserValue :: !a
- deserPos :: !(Len Bool Word)
- module Database.Perdure.Persistent
- data CRef r a
- onCRef :: (r a -> b) -> (a -> b) -> CRef r a -> b
- module Cgm.Control.Concurrent.NotificationCount
- prnf :: Persister a -> a -> ()
- class SyncableStoreFile f => StoreFile f where
- type StoreRef f :: * -> *
- storeFileWrite :: Endian w => f -> Len Word64 Word64 -> Endianness -> [PrimArray Pinned w] -> IO (StoreRef f w)
- storeFileRead :: (Validator v, ValidatedElem v ~ w, Endian w, LgMultiple w Word8) => f -> StoreRef f w -> Endianness -> v -> Async (Maybe (ArrayRange (PrimArray Pinned w))) ()
- class SyncableStoreFile f where
- storeFileSync :: f -> IO () -> IO ()
- storeFileFullBarrier :: f -> IO ()
- await0 :: (IO () -> IO a) -> IO a
- await1 :: Async a () -> IO a
- refSpan :: forall w. LgMultiple Word64 w => BasicRef w -> Span
- data Word64
- data BasicRef w = BasicRef {}
- module Foreign.Ptr
- module Cgm.Data.Len
- data PState a
- data Root a = Root {
- rootId :: StateId
- rootDecr :: Maybe (RootValues a)
- rootScan :: RootValues a
- data RootValues a = RootValues {}
- rootAllocSize :: Len Word64 Word32
- initState :: (Persistent a, Typeable a) => RootLocation -> SpaceTree -> a -> IO (PState a)
- readState :: (Persistent a, Typeable a) => RootLocation -> IO (Maybe (PState a))
- writeState :: (Persistent a, Typeable a) => a -> PState a -> IO (PState a)
- updateState :: (Persistent a, Typeable a, MonadIO m) => StateT a m b -> StateT (PState a) m b
- updateStateRead :: (Persistent a, Typeable a, MonadIO m) => StateT a (ReaderT (PState a) m) b -> StateT (PState a) m b
- collectState :: (Persistent a, Typeable a) => PState a -> IO (PState a)
- collectStateM :: (Persistent a, Typeable a) => StateT (PState a) IO ()
- class Space a where
- emptySpace :: a
- removeSpan :: Span -> a -> a
- addSpan :: Span -> a -> a
- findSpan :: Word64 -> a -> [Span]
- isFreeSpace :: Word64 -> a -> Bool
- type Span = SortedPair Word64
- module Cgm.Data.SortedPair
- module Data.Monoid
- module Database.Perdure.Persistent
- data CachedFile = CachedFile ReplicatedFile (MVar Cache)
- data RootLocation = RootLocation CachedFile [RootAddress]
- newtype RootAddress = RootAddress {}
- stateValue :: PState a -> a
- incr :: Persister a -> a -> SpaceBook -> SpaceBook
- decr :: Persister a -> a -> SpaceBook -> SpaceBook
- data MapMultiset a
- module Cgm.Data.Multiset
- data SpaceBook = SpaceBook {
- bookCount :: !(MapMultiset Address)
- bookSpace :: !SpaceTree
Documentation
type SerializerContext l c = (MVar Cache, l, CountDest c)Source
cSer :: (Multiset c, Allocator l) => Persister a -> SerializerContext l c -> (a -> Dest -> IO z) -> a -> Dest -> IO zSource
serializeToArray :: AllocCopy w => Persister a -> a -> PrimArray Pinned wSource
The passed Persister must hace no references
cDeser :: Persister a -> DeserializerContext -> Deserializer Free aSource
deserializeFromArray :: (Allocation f, Allocation df, Deserializable w) => Deserializer df a -> ArrayRange (PrimArray f w) -> DeserOut aSource
deserializeFromFullArray :: forall f df w a. (Allocation f, Allocation df, Deserializable w, LgMultiple w Bool, Prim w) => Deserializer df a -> ArrayRange (PrimArray f w) -> aSource
unsafeSeqDeserializer :: Persister a -> Deserializer Free aSource
The passed persister must have no references
newtype Deserializer f a Source
Monad (Deserializer f) | |
Functor (Deserializer f) | |
Functor (Deserializer f) => Applicative (Deserializer f) | |
InjectionACofunctor (Deserializer f) |
class Deserializable a whereSource
deserInput :: (Allocation f, Allocation f') => ArrayRange (PrimArray f a) -> ArrayRange (PrimArray f' Word)Source
module Database.Perdure.Persistent
Deref r => Functor (CRef r) | |
(RefPersistent r, Persistent1 r) => Persistent1 (CRef r) | |
RefPersistent r => RefPersistent (CRef r) | |
Deref r => Deref (CRef r) | |
(Deref (CRef r), Deref r) => Ref (CRef r) | |
(Deref r, Eq a) => Eq (CRef r a) | |
(Deref r, Show a) => Show (CRef r a) | |
(Typeable1 r, Typeable a) => Typeable (CRef r a) | |
(RefPersistent r, Persistent1 r, Typeable a, Persistent a) => Persistent (CRef r a) |
class SyncableStoreFile f => StoreFile f whereSource
storeFileWrite :: Endian w => f -> Len Word64 Word64 -> Endianness -> [PrimArray Pinned w] -> IO (StoreRef f w)Source
storeFileRead :: (Validator v, ValidatedElem v ~ w, Endian w, LgMultiple w Word8) => f -> StoreRef f w -> Endianness -> v -> Async (Maybe (ArrayRange (PrimArray Pinned w))) ()Source
StoreFile ReplicatedFile | |
(SyncableStoreFile (SingleStoreFile a), RawStoreFile a) => StoreFile (SingleStoreFile a) |
class SyncableStoreFile f whereSource
storeFileSync :: f -> IO () -> IO ()Source
Notify when all preceeding writes have completed, implies no barrier
storeFileFullBarrier :: f -> IO ()Source
Prevent the reordering of preceeding and subsequent read and write operations
SyncableStoreFile LocalStoreFile | |
SyncableStoreFile ReplicatedFile | |
SyncableStoreFile a => SyncableStoreFile (SingleStoreFile a) |
data Word64
64-bit unsigned integer type
module Foreign.Ptr
module Cgm.Data.Len
The PState represents the whole state of the database. It is needed to perform updates.
Root persisted data. The a
type parameter is the user persisted data type.
Root | |
|
Structured (Root a0) | |
(Persistent a, Typeable a) => Persistent (Root a) |
data RootValues a Source
Structured (RootValues a0) | |
(Persistent a, Typeable a) => Persistent (RootValues a) |
rootAllocSize :: Len Word64 Word32Source
We reserve the option of growing roots to 1MB, so use this as a minimum distance between the various RootAddress in RootLocation
initState :: (Persistent a, Typeable a) => RootLocation -> SpaceTree -> a -> IO (PState a)Source
Writes an initial state (creates a new database).
Most often the passed a
will be a fresh unpersisted value. This is always safe.
However it is legal for parts of a
to be already persisted, but they must only use allocations within the passed SpaceTree.
To read the state of an existing database use readState.
readState :: (Persistent a, Typeable a) => RootLocation -> IO (Maybe (PState a))Source
Reads the state of an existing database. It only reads the root, and the rest is lazy loaded. The RootLocation must match the one use when writing. On failure it returns Nothing.
writeState :: (Persistent a, Typeable a) => a -> PState a -> IO (PState a)Source
Takes the current state and the new value to be written, and writes and returns a new state. Writing is strict so make sure you do not have cycles in the value to be written. After writing, you should no longer use the value you passed in, but instead use the equivalent value present in the in the returned state. That new equivalent value knows where it is stored and will be lazily loadable. The value just written will be partially or totally in the cache. IMPORTANT: This call overwrites the value that was in the state passed as input, so you should not use it after this call returns. However it is safe for this call to use it implicitly, because often the new value will be a function of the old one, and the strict write process will force parts of the old value to be read. If by accident you do use a value which was overwritten, its digests will be incorrect (with very high probability) and deref will return error. This calls collectState implicity once every 1000 calls. We will make this optional in future revisions.
updateState :: (Persistent a, Typeable a, MonadIO m) => StateT a m b -> StateT (PState a) m bSource
Writes a new state if the passed state change requires it. The StateT monad used here is like the usual StateT monad but
it has an additional unchanged
case which allow us to avoid needless writes.
updateStateRead :: (Persistent a, Typeable a, MonadIO m) => StateT a (ReaderT (PState a) m) b -> StateT (PState a) m bSource
Like updateState but the updater has access to the input PState throught an additional ReaderT
collectState :: (Persistent a, Typeable a) => PState a -> IO (PState a)Source
Collects the garbage accumulated by the calls to writeState. Uses reference counting: first does an increment pass on the current value, and then does a decrement pass on the value that was present at the last collection. Only new allocations are scanned in the increment pass, not what was already allocated at the last collection. The decrement pass only traverses the allocations that need to be deallocated.
collectStateM :: (Persistent a, Typeable a) => StateT (PState a) IO ()Source
emptySpace :: aSource
removeSpan :: Span -> a -> aSource
addSpan :: Span -> a -> aSource
findSpan :: Word64 -> a -> [Span]Source
isFreeSpace :: Word64 -> a -> BoolSource
Space SpaceTree |
type Span = SortedPair Word64Source
module Cgm.Data.SortedPair
module Data.Monoid
module Database.Perdure.Persistent
data RootLocation Source
The RootLocation specifies where roots are written, and provides a cache.
stateValue :: PState a -> aSource
decr :: Persister a -> a -> SpaceBook -> SpaceBookSource
Has effects through unsafePerformIO on the caches stored in the DRefs (removes any cache entries for the deallocated allocations).
data MapMultiset a Source
Typeable1 MapMultiset | |
Multiset MapMultiset | |
Structured (MapMultiset a0) | |
(Typeable a, Persistent a) => Persistent (MapMultiset a) |
module Cgm.Data.Multiset
SpaceBook | |
|