Safe Haskell | None |
---|---|
Language | Haskell2010 |
ContentHashable
provides a hashing function suitable for use in the
Funflow content store.
This behaves as does a normal hashing function on Haskell types. However, on path types, this instead calculates a hash based on the contents of the file or directory referenced.
We also export the ExternallyAssuredFile
and ExternallyAssuredDirectory
types. These instead use the path, file size and modification time to control
the hash.
Synopsis
- data ContentHash
- toBytes :: ContentHash -> ByteString
- fromBytes :: ByteString -> Maybe ContentHash
- class Monad m => ContentHashable m a where
- contentHashUpdate :: Context SHA256 -> a -> m (Context SHA256)
- contentHash :: a -> m ContentHash
- contentHashUpdate_binaryFile :: Context SHA256 -> FilePath -> IO (Context SHA256)
- contentHashUpdate_byteArray# :: ByteArray# -> Int -> Int -> Context SHA256 -> Context SHA256
- contentHashUpdate_fingerprint :: (Monad m, Typeable a) => Context SHA256 -> a -> m (Context SHA256)
- contentHashUpdate_primitive :: (Monad m, Typeable a, Storable a) => Context SHA256 -> a -> m (Context SHA256)
- contentHashUpdate_storable :: (Monad m, Storable a) => Context SHA256 -> a -> m (Context SHA256)
- newtype FileContent = FileContent (Path Abs File)
- newtype DirectoryContent = DirectoryContent (Path Abs Dir)
- newtype ExternallyAssuredFile = ExternallyAssuredFile (Path Abs File)
- newtype ExternallyAssuredDirectory = ExternallyAssuredDirectory (Path Abs Dir)
- encodeHash :: ContentHash -> ByteString
- decodeHash :: ByteString -> Maybe ContentHash
- hashToPath :: ContentHash -> Path Rel Dir
- pathToHash :: FilePath -> Maybe ContentHash
- data SHA256
- data Context a
- data Digest a
Documentation
data ContentHash Source #
Instances
toBytes :: ContentHash -> ByteString Source #
fromBytes :: ByteString -> Maybe ContentHash Source #
class Monad m => ContentHashable m a where Source #
Nothing
contentHashUpdate :: Context SHA256 -> a -> m (Context SHA256) Source #
contentHashUpdate :: (Generic a, GContentHashable m (Rep a)) => Context SHA256 -> a -> m (Context SHA256) Source #
contentHash :: a -> m ContentHash Source #
Generate hash of the given value.
See hash
.
Instances
contentHashUpdate_binaryFile :: Context SHA256 -> FilePath -> IO (Context SHA256) Source #
Update hash context based on binary contents of the given file.
contentHashUpdate_byteArray# :: ByteArray# -> Int -> Int -> Context SHA256 -> Context SHA256 Source #
Update hash context based on ByteArray#
by copying into a newly allocated Bytes
and updating the hash context from there.
XXX:
could be used together with byteArrayContents#
:: ByteArray#
-> Addr#
MemView
instead.
However, byteArrayContents#
explicitly says, that it is only safe to use
on a pinned ByteArray#
.
contentHashUpdate_fingerprint :: (Monad m, Typeable a) => Context SHA256 -> a -> m (Context SHA256) Source #
Update hash context based on a type's Fingerprint
.
The fingerprint is constructed from the library-name, module-name, and name of the type itself.
contentHashUpdate_primitive :: (Monad m, Typeable a, Storable a) => Context SHA256 -> a -> m (Context SHA256) Source #
Update hash context by combining contentHashUpdate_fingerprint
and contentHashUpdate_storable
.
Intended for primitive types like Int
.
contentHashUpdate_storable :: (Monad m, Storable a) => Context SHA256 -> a -> m (Context SHA256) Source #
Update hash context based on binary in memory representation due to Storable
.
XXX: Do we need to worry about endianness?
newtype FileContent Source #
Path to a regular file
Only the file's content and its executable permission is taken into account when generating the content hash. The path itself is ignored.
Instances
ContentHashable IO FileContent Source # | |
Defined in Data.CAS.ContentHashable contentHashUpdate :: Context SHA256 -> FileContent -> IO (Context SHA256) Source # contentHash :: FileContent -> IO ContentHash Source # |
newtype DirectoryContent Source #
Path to a directory
Only the contents of the directory and their path relative to the directory are taken into account when generating the content hash. The path to the directory is ignored.
Instances
MonadIO m => ContentHashable m DirectoryContent Source # | |
Defined in Data.CAS.ContentHashable contentHashUpdate :: Context SHA256 -> DirectoryContent -> m (Context SHA256) Source # contentHash :: DirectoryContent -> m ContentHash Source # |
newtype ExternallyAssuredFile Source #
Path to a file to be treated as _externally assured_.
An externally assured file is handled in a somewhat cheating
way by
funflow. The ContentHashable
instance for such assumes that some external
agent guarantees the integrity of the file being referenced. Thus, rather
than hashing the file contents, we only consider its (absolute) path, size and
modification time, which can be rapidly looked up from filesystem metadata.
For a similar approach, see the instance for ObjectInBucket
in
Control.Funflow.AWS.S3, where we exploit the fact that S3 is already
content hashed to avoid performing any hashing.
Instances
newtype ExternallyAssuredDirectory Source #
Path to a directory to be treated as _externally assured_.
For an externally assured directory, we _do_ traverse its contents and verify those as we would externally assured files, rather than just relying on the directory path. Doing this traversal is pretty cheap, and it's quite likely for directory contents to be modified without modifying the contents.
If an item in the directory cannot be read due to lacking permissions, then it will be ignored and not included in the hash. If the flow does not have permissions to access the contents of a subdirectory, then these contents cannot influence the outcome of a task and it is okay to exclude them from the hash. In that case we only hash the name, as that could influence the outcome of a task.
Instances
encodeHash :: ContentHash -> ByteString Source #
File path appropriate encoding of a hash
decodeHash :: ByteString -> Maybe ContentHash Source #
Inverse of encodeHash
if given a valid input.
decodeHash (encodeHash x) = Just x
hashToPath :: ContentHash -> Path Rel Dir Source #
File path appropriate encoding of a hash
pathToHash :: FilePath -> Maybe ContentHash Source #
Inverse of hashToPath
if given a valid input.
pathToHash (hashToPath x) = Just x
SHA256 cryptographic hash algorithm
Instances
Data SHA256 | |
Defined in Crypto.Hash.SHA256 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |
Show SHA256 | |
HashAlgorithm SHA256 | |
Defined in Crypto.Hash.SHA256 type HashBlockSize SHA256 :: Nat # type HashDigestSize SHA256 :: Nat # type HashInternalContextSize SHA256 :: Nat # hashBlockSize :: SHA256 -> Int # hashDigestSize :: SHA256 -> Int # hashInternalContextSize :: SHA256 -> Int # hashInternalInit :: Ptr (Context SHA256) -> IO () # hashInternalUpdate :: Ptr (Context SHA256) -> Ptr Word8 -> Word32 -> IO () # hashInternalFinalize :: Ptr (Context SHA256) -> Ptr (Digest SHA256) -> IO () # | |
type HashInternalContextSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashDigestSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashBlockSize SHA256 | |
Defined in Crypto.Hash.SHA256 |
Represent a context for a given hash algorithm.
Instances
NFData (Context a) | |
Defined in Crypto.Hash.Types | |
ByteArrayAccess (Context a) | |
Represent a digest for a given hash algorithm.
This type is an instance of ByteArrayAccess
from package
memory.
Module Data.ByteArray provides many primitives to work with those values
including conversion to other types.
Creating a digest from a bytearray is also possible with function
digestFromByteString
.
Instances
Eq (Digest a) | |
Data a => Data (Digest a) | |
Defined in Crypto.Hash.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Digest a -> c (Digest a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Digest a) # toConstr :: Digest a -> Constr # dataTypeOf :: Digest a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Digest a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Digest a)) # gmapT :: (forall b. Data b => b -> b) -> Digest a -> Digest a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Digest a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Digest a -> r # gmapQ :: (forall d. Data d => d -> u) -> Digest a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Digest a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # | |
Ord (Digest a) | |
Defined in Crypto.Hash.Types | |
HashAlgorithm a => Read (Digest a) | |
Show (Digest a) | |
NFData (Digest a) | |
Defined in Crypto.Hash.Types | |
ByteArrayAccess (Digest a) | |