| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Erebos.Storage.Internal
Documentation
Constructors
| Storage | |
Fields | |
showParentStorage :: Storage' c -> String Source #
data StorageBacking c Source #
Constructors
| StorageDir | |
Fields
| |
| StorageMemory | |
Fields
| |
Instances
| Eq (StorageBacking c) Source # | |
Defined in Erebos.Storage.Internal Methods (==) :: StorageBacking c -> StorageBacking c -> Bool # (/=) :: StorageBacking c -> StorageBacking c -> Bool # | |
data WatchListItem c Source #
Constructors
| WatchListItem | |
Constructors
| RefDigest (Digest Blake2b_256) |
Instances
| Show RefDigest Source # | |
| NFData RefDigest Source # | |
Defined in Erebos.Storage.Internal | |
| StorageCompleteness Partial Source # | |
Defined in Erebos.Storage.Internal Associated Types type LoadResult Partial a Source # Methods returnLoadResult :: Partial a -> LoadResult Partial a Source # ioLoadBytes :: Ref' Partial -> IO (Partial ByteString) Source # | |
| Eq RefDigest Source # | |
| Ord RefDigest Source # | |
| Hashable RefDigest Source # | |
Defined in Erebos.Storage.Internal | |
| ByteArrayAccess RefDigest Source # | |
| type LoadResult Partial a Source # | |
Defined in Erebos.Storage.Internal | |
refStorage :: Ref' c -> Storage' c Source #
showRef :: Ref' c -> ByteString Source #
showRefDigestParts :: RefDigest -> (ByteString, ByteString) Source #
showRefDigest :: RefDigest -> ByteString Source #
readRefDigest :: ByteString -> Maybe RefDigest Source #
refDigestFromByteString :: ByteArrayAccess ba => ba -> Maybe RefDigest Source #
showHex :: ByteArrayAccess ba => ba -> ByteString Source #
newtype Generation Source #
Constructors
| Generation Int |
Instances
| Show Generation Source # | |
Defined in Erebos.Storage.Internal Methods showsPrec :: Int -> Generation -> ShowS # show :: Generation -> String # showList :: [Generation] -> ShowS # | |
| Eq Generation Source # | |
Defined in Erebos.Storage.Internal | |
newtype HeadTypeID Source #
Constructors
| HeadTypeID UUID |
Instances
| StorableUUID HeadTypeID Source # | |
Defined in Erebos.Storage | |
| Eq HeadTypeID Source # | |
Defined in Erebos.Storage.Internal | |
| Ord HeadTypeID Source # | |
Defined in Erebos.Storage.Internal Methods compare :: HeadTypeID -> HeadTypeID -> Ordering # (<) :: HeadTypeID -> HeadTypeID -> Bool # (<=) :: HeadTypeID -> HeadTypeID -> Bool # (>) :: HeadTypeID -> HeadTypeID -> Bool # (>=) :: HeadTypeID -> HeadTypeID -> Bool # max :: HeadTypeID -> HeadTypeID -> HeadTypeID # min :: HeadTypeID -> HeadTypeID -> HeadTypeID # | |
Instances
| Storable a => Storable (Stored a) Source # | |
| ZeroStorable a => ZeroStorable (Stored a) Source # | |
| Mergeable [Stored Object] Source # | |
| Show a => Show (Stored' c a) Source # | |
| Eq (Stored' c a) Source # | |
| Ord (Stored' c a) Source # | |
Defined in Erebos.Storage.Internal | |
| type Component [Stored Object] Source # | |
Defined in Erebos.Storage.Merge | |
storedStorage :: Stored' c a -> Storage' c Source #
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 #
Instances
| StorageCompleteness Complete Source # | |
Defined in Erebos.Storage.Internal Associated Types type LoadResult Complete a Source # Methods returnLoadResult :: Complete a -> LoadResult Complete a Source # ioLoadBytes :: Ref' Complete -> IO (Complete ByteString) Source # | |
| StorageCompleteness Partial Source # | |
Defined in Erebos.Storage.Internal Associated Types type LoadResult Partial a Source # Methods returnLoadResult :: Partial a -> LoadResult Partial a Source # ioLoadBytes :: Ref' Partial -> IO (Partial ByteString) Source # | |
unsafeStoreRawBytes :: Storage' c -> ByteString -> IO (Ref' c) Source #
ioLoadBytesFromStorage :: Storage' c -> RefDigest -> IO (Maybe ByteString) Source #
writeFileOnce :: FilePath -> ByteString -> IO () Source #
writeFileChecked :: FilePath -> Maybe ByteString -> ByteString -> IO (Either (Maybe ByteString) ()) Source #