Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Storage = Storage' Complete
- type PartialStorage = Storage' Partial
- class (Traversable compl, Monad compl) => StorageCompleteness compl
- openStorage :: FilePath -> IO Storage
- memoryStorage :: IO Storage
- deriveEphemeralStorage :: Storage -> IO Storage
- derivePartialStorage :: Storage -> IO PartialStorage
- type Ref = Ref' Complete
- type PartialRef = Ref' Partial
- data RefDigest
- refDigest :: Ref' c -> RefDigest
- readRef :: Storage -> ByteString -> IO (Maybe Ref)
- showRef :: Ref' c -> ByteString
- showRefDigest :: RefDigest -> ByteString
- refDigestFromByteString :: ByteArrayAccess ba => ba -> Maybe RefDigest
- hashToRefDigest :: ByteString -> RefDigest
- copyRef :: forall c c' m. (StorageCompleteness c, StorageCompleteness c', MonadIO m) => Storage' c' -> Ref' c -> m (LoadResult c (Ref' c'))
- partialRef :: PartialStorage -> Ref -> PartialRef
- partialRefFromDigest :: PartialStorage -> RefDigest -> PartialRef
- type Object = Object' Complete
- type PartialObject = Object' Partial
- data Object' c
- = Blob ByteString
- | Rec [(ByteString, RecItem' c)]
- | ZeroObject
- | UnknownObject ByteString ByteString
- type RecItem = RecItem' Complete
- data RecItem' c
- serializeObject :: Object' c -> ByteString
- deserializeObject :: PartialStorage -> ByteString -> Except String (PartialObject, ByteString)
- deserializeObjects :: PartialStorage -> ByteString -> Except String [PartialObject]
- ioLoadObject :: forall c. StorageCompleteness c => Ref' c -> IO (c (Object' c))
- ioLoadBytes :: StorageCompleteness compl => Ref' compl -> IO (compl ByteString)
- storeRawBytes :: PartialStorage -> ByteString -> IO PartialRef
- lazyLoadBytes :: forall c. StorageCompleteness c => Ref' c -> LoadResult c ByteString
- storeObject :: PartialStorage -> PartialObject -> IO PartialRef
- collectObjects :: Object -> [Object]
- collectStoredObjects :: Stored Object -> [Stored Object]
- type Head = Head' Complete
- class Storable a => HeadType a where
- headTypeID :: proxy a -> HeadTypeID
- data HeadTypeID
- mkHeadTypeID :: String -> HeadTypeID
- headId :: Head a -> HeadID
- headStorage :: Head a -> Storage
- headRef :: Head a -> Ref
- headObject :: Head a -> a
- headStoredObject :: Head a -> Stored a
- loadHeads :: forall a m. MonadIO m => HeadType a => Storage -> m [Head a]
- loadHead :: forall a m. (HeadType a, MonadIO m) => Storage -> HeadID -> m (Maybe (Head a))
- reloadHead :: (HeadType a, MonadIO m) => Head a -> m (Maybe (Head a))
- storeHead :: forall a m. MonadIO m => HeadType a => Storage -> a -> m (Head a)
- replaceHead :: forall a m. (HeadType a, MonadIO m) => Head a -> Stored a -> m (Either (Maybe (Head a)) (Head a))
- updateHead :: (HeadType a, MonadIO m) => Head a -> (Stored a -> m (Stored a, b)) -> m (Maybe (Head a), b)
- updateHead_ :: (HeadType a, MonadIO m) => Head a -> (Stored a -> m (Stored a)) -> m (Maybe (Head a))
- loadHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> HeadID -> m (Maybe Ref)
- storeHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> Ref -> m HeadID
- replaceHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> HeadID -> Ref -> Ref -> m (Either (Maybe Ref) Ref)
- data WatchedHead
- watchHead :: forall a. HeadType a => Head a -> (Head a -> IO ()) -> IO WatchedHead
- watchHeadWith :: forall a b. (HeadType a, Eq b) => Head a -> (Head a -> b) -> (b -> IO ()) -> IO WatchedHead
- unwatchHead :: WatchedHead -> IO ()
- watchHeadRaw :: forall b. Eq b => Storage -> HeadTypeID -> HeadID -> (Ref -> b) -> (b -> IO ()) -> IO WatchedHead
- class Monad m => MonadStorage m where
- getStorage :: m Storage
- mstore :: Storable a => a -> m (Stored a)
- class Storable a where
- class Storable a => ZeroStorable a where
- class StorableText a where
- class StorableDate a where
- class StorableUUID a where
- data Store
- type StoreRec c = StoreRecM c ()
- evalStore :: StorageCompleteness c => Storage' c -> Store -> IO (Ref' c)
- evalStoreObject :: StorageCompleteness c => Storage' c -> Store -> IO (Object' c)
- storeBlob :: ByteString -> Store
- storeRec :: (forall c. StorageCompleteness c => StoreRec c) -> Store
- storeZero :: Store
- storeEmpty :: String -> StoreRec c
- storeInt :: Integral a => String -> a -> StoreRec c
- storeNum :: (Real a, Fractional a) => String -> a -> StoreRec c
- storeText :: StorableText a => String -> a -> StoreRec c
- storeBinary :: ByteArrayAccess a => String -> a -> StoreRec c
- storeDate :: StorableDate a => String -> a -> StoreRec c
- storeUUID :: StorableUUID a => String -> a -> StoreRec c
- storeRef :: Storable a => StorageCompleteness c => String -> a -> StoreRec c
- storeRawRef :: StorageCompleteness c => String -> Ref -> StoreRec c
- storeMbEmpty :: String -> Maybe () -> StoreRec c
- storeMbInt :: Integral a => String -> Maybe a -> StoreRec c
- storeMbNum :: (Real a, Fractional a) => String -> Maybe a -> StoreRec c
- storeMbText :: StorableText a => String -> Maybe a -> StoreRec c
- storeMbBinary :: ByteArrayAccess a => String -> Maybe a -> StoreRec c
- storeMbDate :: StorableDate a => String -> Maybe a -> StoreRec c
- storeMbUUID :: StorableUUID a => String -> Maybe a -> StoreRec c
- storeMbRef :: Storable a => StorageCompleteness c => String -> Maybe a -> StoreRec c
- storeMbRawRef :: StorageCompleteness c => String -> Maybe Ref -> StoreRec c
- storeZRef :: (ZeroStorable a, StorageCompleteness c) => String -> a -> StoreRec c
- storeRecItems :: StorageCompleteness c => [(ByteString, RecItem)] -> StoreRec c
- data Load a
- data LoadRec a
- evalLoad :: Load a -> Ref -> a
- loadCurrentRef :: Load Ref
- loadCurrentObject :: Load Object
- loadRecCurrentRef :: LoadRec Ref
- loadRecItems :: LoadRec [(ByteString, RecItem)]
- loadBlob :: (ByteString -> a) -> Load a
- loadRec :: LoadRec a -> Load a
- loadZero :: a -> Load a
- loadEmpty :: String -> LoadRec ()
- loadInt :: Num a => String -> LoadRec a
- loadNum :: (Real a, Fractional a) => String -> LoadRec a
- loadText :: StorableText a => String -> LoadRec a
- loadBinary :: ByteArray a => String -> LoadRec a
- loadDate :: StorableDate a => String -> LoadRec a
- loadUUID :: StorableUUID a => String -> LoadRec a
- loadRef :: Storable a => String -> LoadRec a
- loadRawRef :: String -> LoadRec Ref
- loadMbEmpty :: String -> LoadRec (Maybe ())
- loadMbInt :: Num a => String -> LoadRec (Maybe a)
- loadMbNum :: (Real a, Fractional a) => String -> LoadRec (Maybe a)
- loadMbText :: StorableText a => String -> LoadRec (Maybe a)
- loadMbBinary :: ByteArray a => String -> LoadRec (Maybe a)
- loadMbDate :: StorableDate a => String -> LoadRec (Maybe a)
- loadMbUUID :: StorableUUID a => String -> LoadRec (Maybe a)
- loadMbRef :: Storable a => String -> LoadRec (Maybe a)
- loadMbRawRef :: String -> LoadRec (Maybe Ref)
- loadTexts :: StorableText a => String -> LoadRec [a]
- loadBinaries :: ByteArray a => String -> LoadRec [a]
- loadRefs :: Storable a => String -> LoadRec [a]
- loadRawRefs :: String -> LoadRec [Ref]
- loadZRef :: ZeroStorable a => String -> LoadRec a
- type Stored a = Stored' Complete a
- fromStored :: Stored a -> a
- storedRef :: Stored a -> Ref
- wrappedStore :: MonadIO m => Storable a => Storage -> a -> m (Stored a)
- wrappedLoad :: Storable a => Ref -> Stored a
- copyStored :: forall c c' m a. (StorageCompleteness c, StorageCompleteness c', MonadIO m) => Storage' c' -> Stored' c a -> m (LoadResult c (Stored' c' a))
- unsafeMapStored :: (a -> b) -> Stored a -> Stored b
- data StoreInfo = StoreInfo {}
- makeStoreInfo :: IO StoreInfo
- type StoredHistory a = Stored (History a)
- fromHistory :: StoredHistory a -> a
- fromHistoryAt :: ZonedTime -> StoredHistory a -> Maybe a
- storedFromHistory :: StoredHistory a -> Stored a
- storedHistoryList :: StoredHistory a -> [Stored a]
- beginHistory :: Storable a => Storage -> StoreInfo -> a -> IO (StoredHistory a)
- modifyHistory :: Storable a => StoreInfo -> (a -> a) -> StoredHistory a -> IO (StoredHistory a)
Documentation
type PartialStorage = Storage' Partial Source #
class (Traversable compl, Monad compl) => StorageCompleteness compl Source #
Instances
StorageCompleteness Complete Source # | |
Defined in Erebos.Storage.Internal type LoadResult Complete a Source # returnLoadResult :: Complete a -> LoadResult Complete a Source # ioLoadBytes :: Ref' Complete -> IO (Complete ByteString) Source # | |
StorageCompleteness Partial Source # | |
Defined in Erebos.Storage.Internal type LoadResult Partial a Source # returnLoadResult :: Partial a -> LoadResult Partial a Source # ioLoadBytes :: Ref' Partial -> IO (Partial ByteString) Source # |
type PartialRef = Ref' Partial Source #
Instances
Show RefDigest Source # | |
NFData RefDigest Source # | |
Defined in Erebos.Storage.Internal | |
StorageCompleteness Partial Source # | |
Defined in Erebos.Storage.Internal type LoadResult Partial a Source # returnLoadResult :: Partial a -> LoadResult Partial a Source # ioLoadBytes :: Ref' Partial -> IO (Partial ByteString) Source # | |
Eq RefDigest Source # | |
Ord RefDigest Source # | |
Defined in Erebos.Storage.Internal | |
Hashable RefDigest Source # | |
Defined in Erebos.Storage.Internal | |
ByteArrayAccess RefDigest Source # | |
type LoadResult Partial a Source # | |
Defined in Erebos.Storage.Internal |
showRef :: Ref' c -> ByteString Source #
showRefDigest :: RefDigest -> ByteString Source #
refDigestFromByteString :: ByteArrayAccess ba => ba -> Maybe RefDigest Source #
copyRef :: forall c c' m. (StorageCompleteness c, StorageCompleteness c', MonadIO m) => Storage' c' -> Ref' c -> m (LoadResult c (Ref' c')) Source #
partialRef :: PartialStorage -> Ref -> PartialRef Source #
type PartialObject = Object' Partial Source #
serializeObject :: Object' c -> ByteString Source #
deserializeObject :: PartialStorage -> ByteString -> Except String (PartialObject, ByteString) Source #
ioLoadObject :: forall c. StorageCompleteness c => Ref' c -> IO (c (Object' c)) Source #
ioLoadBytes :: StorageCompleteness compl => Ref' compl -> IO (compl ByteString) Source #
storeRawBytes :: PartialStorage -> ByteString -> IO PartialRef Source #
lazyLoadBytes :: forall c. StorageCompleteness c => Ref' c -> LoadResult c ByteString Source #
storeObject :: PartialStorage -> PartialObject -> IO PartialRef Source #
collectObjects :: Object -> [Object] Source #
class Storable a => HeadType a where Source #
headTypeID :: proxy a -> HeadTypeID Source #
Instances
HeadType LocalState Source # | |
Defined in Erebos.State headTypeID :: proxy LocalState -> HeadTypeID Source # |
data HeadTypeID Source #
Instances
StorableUUID HeadTypeID Source # | |
Defined in Erebos.Storage toUUID :: HeadTypeID -> UUID Source # fromUUID :: UUID -> HeadTypeID Source # | |
Eq HeadTypeID Source # | |
Defined in Erebos.Storage.Internal (==) :: HeadTypeID -> HeadTypeID -> Bool # (/=) :: HeadTypeID -> HeadTypeID -> Bool # | |
Ord HeadTypeID Source # | |
Defined in Erebos.Storage.Internal compare :: HeadTypeID -> HeadTypeID -> Ordering # (<) :: HeadTypeID -> HeadTypeID -> Bool # (<=) :: HeadTypeID -> HeadTypeID -> Bool # (>) :: HeadTypeID -> HeadTypeID -> Bool # (>=) :: HeadTypeID -> HeadTypeID -> Bool # max :: HeadTypeID -> HeadTypeID -> HeadTypeID # min :: HeadTypeID -> HeadTypeID -> HeadTypeID # |
mkHeadTypeID :: String -> HeadTypeID Source #
headStorage :: Head a -> Storage Source #
headObject :: Head a -> a Source #
headStoredObject :: Head a -> Stored a Source #
replaceHead :: forall a m. (HeadType a, MonadIO m) => Head a -> Stored a -> m (Either (Maybe (Head a)) (Head a)) Source #
updateHead :: (HeadType a, MonadIO m) => Head a -> (Stored a -> m (Stored a, b)) -> m (Maybe (Head a), b) Source #
updateHead_ :: (HeadType a, MonadIO m) => Head a -> (Stored a -> m (Stored a)) -> m (Maybe (Head a)) Source #
loadHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> HeadID -> m (Maybe Ref) Source #
storeHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> Ref -> m HeadID Source #
replaceHeadRaw :: forall m. MonadIO m => Storage -> HeadTypeID -> HeadID -> Ref -> Ref -> m (Either (Maybe Ref) Ref) Source #
data WatchedHead Source #
watchHeadWith :: forall a b. (HeadType a, Eq b) => Head a -> (Head a -> b) -> (b -> IO ()) -> IO WatchedHead Source #
unwatchHead :: WatchedHead -> IO () Source #
watchHeadRaw :: forall b. Eq b => Storage -> HeadTypeID -> HeadID -> (Ref -> b) -> (b -> IO ()) -> IO WatchedHead Source #
class Monad m => MonadStorage m where Source #
getStorage :: m Storage Source #
Instances
MonadStorage (ServiceHandler s) Source # | |
Defined in Erebos.Service getStorage :: ServiceHandler s Storage Source # mstore :: Storable a => a -> ServiceHandler s (Stored a) Source # | |
MonadIO m => MonadStorage (ReaderT (Head a) m) Source # | |
MonadIO m => MonadStorage (ReaderT Storage m) Source # | |
class Storable a where Source #
Instances
class Storable a => ZeroStorable a where Source #
Instances
ZeroStorable a => ZeroStorable (Stored a) Source # | |
Storable a => ZeroStorable [a] Source # | |
Defined in Erebos.Storage |
class StorableText a where Source #
Instances
class StorableDate a where Source #
Instances
class StorableUUID a where Source #
Instances
StorableUUID ServiceID Source # | |
StorableUUID SharedTypeID Source # | |
Defined in Erebos.State toUUID :: SharedTypeID -> UUID Source # fromUUID :: UUID -> SharedTypeID Source # | |
StorableUUID HeadID Source # | |
StorableUUID HeadTypeID Source # | |
Defined in Erebos.Storage toUUID :: HeadTypeID -> UUID Source # fromUUID :: UUID -> HeadTypeID Source # | |
StorableUUID UUID Source # | |
evalStoreObject :: StorageCompleteness c => Storage' c -> Store -> IO (Object' c) Source #
storeBlob :: ByteString -> Store Source #
storeEmpty :: String -> StoreRec c Source #
storeBinary :: ByteArrayAccess a => String -> a -> StoreRec c Source #
storeRawRef :: StorageCompleteness c => String -> Ref -> StoreRec c Source #
storeMbNum :: (Real a, Fractional a) => String -> Maybe a -> StoreRec c Source #
storeMbText :: StorableText a => String -> Maybe a -> StoreRec c Source #
storeMbBinary :: ByteArrayAccess a => String -> Maybe a -> StoreRec c Source #
storeMbDate :: StorableDate a => String -> Maybe a -> StoreRec c Source #
storeMbUUID :: StorableUUID a => String -> Maybe a -> StoreRec c Source #
storeMbRef :: Storable a => StorageCompleteness c => String -> Maybe a -> StoreRec c Source #
storeMbRawRef :: StorageCompleteness c => String -> Maybe Ref -> StoreRec c Source #
storeZRef :: (ZeroStorable a, StorageCompleteness c) => String -> a -> StoreRec c Source #
storeRecItems :: StorageCompleteness c => [(ByteString, RecItem)] -> StoreRec c Source #
Instances
loadCurrentRef :: Load Ref Source #
loadRecItems :: LoadRec [(ByteString, RecItem)] Source #
loadBlob :: (ByteString -> a) -> Load a Source #
loadMbText :: StorableText a => String -> LoadRec (Maybe a) Source #
loadMbDate :: StorableDate a => String -> LoadRec (Maybe a) Source #
loadMbUUID :: StorableUUID a => String -> LoadRec (Maybe a) Source #
fromStored :: Stored a -> a Source #
copyStored :: forall c c' m a. (StorageCompleteness c, StorageCompleteness c', MonadIO m) => Storage' c' -> Stored' c a -> m (LoadResult c (Stored' c' a)) Source #
unsafeMapStored :: (a -> b) -> Stored a -> Stored b Source #
Passed function needs to preserve the object representation to be safe
type StoredHistory a = Stored (History a) Source #
fromHistory :: StoredHistory a -> a Source #
fromHistoryAt :: ZonedTime -> StoredHistory a -> Maybe a Source #
storedFromHistory :: StoredHistory a -> Stored a Source #
storedHistoryList :: StoredHistory a -> [Stored a] Source #
beginHistory :: Storable a => Storage -> StoreInfo -> a -> IO (StoredHistory a) Source #
modifyHistory :: Storable a => StoreInfo -> (a -> a) -> StoredHistory a -> IO (StoredHistory a) Source #