perdure-0.2.1: Robust persistence for acyclic immutable data

Safe HaskellNone

Database.Perdure.Internal

Synopsis

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

unsafeSeqDeserializer :: Persister a -> Deserializer Free aSource

The passed persister must have no references

data DeserOut a Source

Constructors

DeserOut 

Fields

deserValue :: !a
 
deserPos :: !(Len Bool Word)
 

Instances

data CRef r a Source

Constructors

Refed !(r a) 
ToRef !a 

Instances

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) 

onCRef :: (r a -> b) -> (a -> b) -> CRef r a -> bSource

prnf :: Persister a -> a -> ()Source

class SyncableStoreFile f => StoreFile f whereSource

Associated Types

type StoreRef f :: * -> *Source

Methods

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

Instances

StoreFile ReplicatedFile 
(SyncableStoreFile (SingleStoreFile a), RawStoreFile a) => StoreFile (SingleStoreFile a) 

class SyncableStoreFile f whereSource

Methods

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

await0 :: (IO () -> IO a) -> IO a

await1 :: Async a () -> IO a

data PState a Source

The PState represents the whole state of the database. It is needed to perform updates.

data Root a Source

Root persisted data. The a type parameter is the user persisted data type.

Constructors

Root 

Fields

rootId :: StateId
 
rootDecr :: Maybe (RootValues a)
 
rootScan :: RootValues a
 

Instances

data RootValues a Source

Constructors

RootValues 

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.

class Space a whereSource

Instances

Space SpaceTree 

data RootLocation Source

The RootLocation specifies where roots are written, and provides a cache.

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).