Safe Haskell | None |
---|---|
Language | Haskell2010 |
Type-safe operations with bytes
-like data.
Synopsis
- class (KnownValue bs, ToT bs ~ ToT ByteString) => BytesLike bs where
- toBytes :: bs -> ByteString
- newtype Packed a = Packed {}
- newtype TSignature a = TSignature {}
- lSign :: (MonadRandom m, BytesLike a) => SecretKey -> a -> m (TSignature a)
- newtype Hash (alg :: HashAlgorithmKind) a = UnsafeHash {
- unHash :: ByteString
- data DHashAlgorithm
- class Typeable alg => KnownHashAlgorithm (alg :: HashAlgorithmKind) where
- hashAlgorithmName :: Proxy alg -> Text
- computeHash :: ByteString -> ByteString
- toHash :: BytesLike bs => (bs ': s) :-> (Hash alg bs ': s)
- toHashHs :: forall alg bs. (BytesLike bs, KnownHashAlgorithm alg) => bs -> Hash alg bs
- data Sha256 :: HashAlgorithmKind
- data Sha512 :: HashAlgorithmKind
- data Blake2b :: HashAlgorithmKind
- data Sha3 :: HashAlgorithmKind
- data Keccak :: HashAlgorithmKind
Documentation
class (KnownValue bs, ToT bs ~ ToT ByteString) => BytesLike bs where Source #
Everything which is represented as bytes inside.
toBytes :: bs -> ByteString Source #
Instances
BytesLike ByteString Source # | |
Defined in Lorentz.Bytes toBytes :: ByteString -> ByteString Source # | |
Typeable a => BytesLike (Packed a) Source # | |
Defined in Lorentz.Bytes toBytes :: Packed a -> ByteString Source # | |
(Typeable alg, Typeable a) => BytesLike (Hash alg a) Source # | |
Defined in Lorentz.Bytes toBytes :: Hash alg a -> ByteString Source # |
Represents a ByteString
resulting from packing a value of type a
.
This is not guaranteed to keep some packed value, and unpack
can fail.
We do so because often we need to accept values of such type from user,
and also because there is no simple way to check validity of packed data
without performing full unpack.
So this wrapper is rather a hint for users.
Instances
newtype TSignature a Source #
Represents a signature, where signed data has given type.
Since we usually sign a packed data, a common pattern for this type is
TSignature (
.
If you don't want to use Packed
signedData)Packed
, use plain TSignature ByteString
instead.
Instances
lSign :: (MonadRandom m, BytesLike a) => SecretKey -> a -> m (TSignature a) Source #
Sign data using SecretKey
newtype Hash (alg :: HashAlgorithmKind) a Source #
Hash of type t
evaluated from data of type a
.
Instances
data DHashAlgorithm Source #
Documentation item for hash algorithms.
Instances
class Typeable alg => KnownHashAlgorithm (alg :: HashAlgorithmKind) where Source #
Hash algorithm used in Tezos.
hashAlgorithmName :: Proxy alg -> Text Source #
computeHash :: ByteString -> ByteString Source #
toHash :: BytesLike bs => (bs ': s) :-> (Hash alg bs ': s) Source #
Instances
toHashHs :: forall alg bs. (BytesLike bs, KnownHashAlgorithm alg) => bs -> Hash alg bs Source #
Evaluate hash in Haskell world.
data Sha256 :: HashAlgorithmKind Source #
Instances
KnownHashAlgorithm Sha256 Source # | |
Defined in Lorentz.Bytes hashAlgorithmName :: Proxy Sha256 -> Text Source # computeHash :: ByteString -> ByteString Source # toHash :: forall bs (s :: [Type]). BytesLike bs => (bs ': s) :-> (Hash Sha256 bs ': s) Source # |
data Sha512 :: HashAlgorithmKind Source #
Instances
KnownHashAlgorithm Sha512 Source # | |
Defined in Lorentz.Bytes hashAlgorithmName :: Proxy Sha512 -> Text Source # computeHash :: ByteString -> ByteString Source # toHash :: forall bs (s :: [Type]). BytesLike bs => (bs ': s) :-> (Hash Sha512 bs ': s) Source # |
data Blake2b :: HashAlgorithmKind Source #
Instances
KnownHashAlgorithm Blake2b Source # | |
Defined in Lorentz.Bytes hashAlgorithmName :: Proxy Blake2b -> Text Source # computeHash :: ByteString -> ByteString Source # toHash :: forall bs (s :: [Type]). BytesLike bs => (bs ': s) :-> (Hash Blake2b bs ': s) Source # |
data Sha3 :: HashAlgorithmKind Source #
Instances
KnownHashAlgorithm Sha3 Source # | |
Defined in Lorentz.Bytes hashAlgorithmName :: Proxy Sha3 -> Text Source # computeHash :: ByteString -> ByteString Source # toHash :: forall bs (s :: [Type]). BytesLike bs => (bs ': s) :-> (Hash Sha3 bs ': s) Source # |
data Keccak :: HashAlgorithmKind Source #
Instances
KnownHashAlgorithm Keccak Source # | |
Defined in Lorentz.Bytes hashAlgorithmName :: Proxy Keccak -> Text Source # computeHash :: ByteString -> ByteString Source # toHash :: forall bs (s :: [Type]). BytesLike bs => (bs ': s) :-> (Hash Keccak bs ': s) Source # |