erebos-0.1.2: Decentralized messaging and synchronization
Safe HaskellSafe-Inferred
LanguageHaskell2010

Erebos.Storage.Internal

Documentation

data Storage' c Source #

Instances

Instances details
Show (Storage' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

showsPrec :: Int -> Storage' c -> ShowS #

show :: Storage' c -> String #

showList :: [Storage' c] -> ShowS #

Eq (Storage' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: Storage' c -> Storage' c -> Bool #

(/=) :: Storage' c -> Storage' c -> Bool #

MonadIO m => MonadStorage (ReaderT Storage m) Source # 
Instance details

Defined in Erebos.Storage

newtype WatchID Source #

Constructors

WatchID Int 

Instances

Instances details
Num WatchID Source # 
Instance details

Defined in Erebos.Storage.Internal

Eq WatchID Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: WatchID -> WatchID -> Bool #

(/=) :: WatchID -> WatchID -> Bool #

Ord WatchID Source # 
Instance details

Defined in Erebos.Storage.Internal

data WatchList c Source #

Constructors

WatchList 

Fields

data WatchListItem c Source #

Constructors

WatchListItem 

Fields

newtype RefDigest Source #

Constructors

RefDigest (Digest Blake2b_256) 

Instances

Instances details
Show RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

NFData RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

rnf :: RefDigest -> () #

StorageCompleteness Partial Source # 
Instance details

Defined in Erebos.Storage.Internal

Associated Types

type LoadResult Partial a Source #

Eq RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

Ord RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

Hashable RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

ByteArrayAccess RefDigest Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

length :: RefDigest -> Int #

withByteArray :: RefDigest -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: RefDigest -> Ptr p -> IO () #

type LoadResult Partial a Source # 
Instance details

Defined in Erebos.Storage.Internal

data Ref' c Source #

Constructors

Ref (Storage' c) RefDigest 

Instances

Instances details
Show (Ref' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

showsPrec :: Int -> Ref' c -> ShowS #

show :: Ref' c -> String #

showList :: [Ref' c] -> ShowS #

Eq (Ref' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: Ref' c -> Ref' c -> Bool #

(/=) :: Ref' c -> Ref' c -> Bool #

Hashable (Ref' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

hashWithSalt :: Int -> Ref' c -> Int #

hash :: Ref' c -> Int #

ByteArrayAccess (Ref' c) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

length :: Ref' c -> Int #

withByteArray :: Ref' c -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Ref' c -> Ptr p -> IO () #

newtype Generation Source #

Constructors

Generation Int 

Instances

Instances details
Show Generation Source # 
Instance details

Defined in Erebos.Storage.Internal

Eq Generation Source # 
Instance details

Defined in Erebos.Storage.Internal

data Head' c a Source #

Constructors

Head HeadID (Stored' c a) 

Instances

Instances details
(HeadType a, MonadIO m) => MonadHead a (ReaderT (Head a) m) Source # 
Instance details

Defined in Erebos.State

Methods

updateLocalHead :: (Stored a -> ReaderT (Head a) m (Stored a, b)) -> ReaderT (Head a) m b Source #

Show a => Show (Head' c a) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

showsPrec :: Int -> Head' c a -> ShowS #

show :: Head' c a -> String #

showList :: [Head' c a] -> ShowS #

MonadIO m => MonadStorage (ReaderT (Head a) m) Source # 
Instance details

Defined in Erebos.Storage

Methods

getStorage :: ReaderT (Head a) m Storage Source #

mstore :: Storable a0 => a0 -> ReaderT (Head a) m (Stored a0) Source #

Eq (Head' c a) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: Head' c a -> Head' c a -> Bool #

(/=) :: Head' c a -> Head' c a -> Bool #

newtype HeadID Source #

Constructors

HeadID UUID 

Instances

Instances details
Show HeadID Source # 
Instance details

Defined in Erebos.Storage.Internal

StorableUUID HeadID Source # 
Instance details

Defined in Erebos.Storage

Eq HeadID Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: HeadID -> HeadID -> Bool #

(/=) :: HeadID -> HeadID -> Bool #

Ord HeadID Source # 
Instance details

Defined in Erebos.Storage.Internal

data Stored' c a Source #

Constructors

Stored (Ref' c) a 

Instances

Instances details
Storable a => Storable (Stored a) Source # 
Instance details

Defined in Erebos.Storage

Methods

store' :: Stored a -> Store Source #

load' :: Load (Stored a) Source #

store :: forall (c :: Type -> Type). StorageCompleteness c => Storage' c -> Stored a -> IO (Ref' c) Source #

load :: Ref -> Stored a Source #

ZeroStorable a => ZeroStorable (Stored a) Source # 
Instance details

Defined in Erebos.Storage

Methods

fromZero :: Storage -> Stored a Source #

Mergeable [Stored Object] Source # 
Instance details

Defined in Erebos.Storage.Merge

Associated Types

type Component [Stored Object] Source #

Show a => Show (Stored' c a) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

showsPrec :: Int -> Stored' c a -> ShowS #

show :: Stored' c a -> String #

showList :: [Stored' c a] -> ShowS #

Eq (Stored' c a) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

(==) :: Stored' c a -> Stored' c a -> Bool #

(/=) :: Stored' c a -> Stored' c a -> Bool #

Ord (Stored' c a) Source # 
Instance details

Defined in Erebos.Storage.Internal

Methods

compare :: Stored' c a -> Stored' c a -> Ordering #

(<) :: Stored' c a -> Stored' c a -> Bool #

(<=) :: Stored' c a -> Stored' c a -> Bool #

(>) :: Stored' c a -> Stored' c a -> Bool #

(>=) :: Stored' c a -> Stored' c a -> Bool #

max :: Stored' c a -> Stored' c a -> Stored' c a #

min :: Stored' c a -> Stored' c a -> Stored' c a #

type Component [Stored Object] Source # 
Instance details

Defined in Erebos.Storage.Merge

class (Traversable compl, Monad compl) => StorageCompleteness compl where Source #

Associated Types

type LoadResult compl a :: Type Source #

Methods

returnLoadResult :: compl a -> LoadResult compl a Source #

ioLoadBytes :: Ref' compl -> IO (compl ByteString) Source #