Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cryptographic primitives used in Tezos.
WARNING: some functions may be vulnerable to timing attacks.
Also, this code was not reviewed by cryptography/security experts.
Do not use it with secret keys that have some value.
We provide SecretKey
type and (limited) signing functionality only
for testing.
If you need to sign something in production, use something else
(e. g. `tezos-client`).
Tezos supports 3 cryptographic curves that are denoted by the number after tz in the public key hash: tz1, tz2 or tz3. • tz1 — ed25519 • tz2 — secp256k1 • tz3 — P256 We have Tezos.Crypto.Curve module for each of these curves. They expose very similar functionality and their main purpose is to hide implementation details for each curve as well as some other specifics (e. g. prefixes that are used for human-readable representation).
This module serves two purposes:
1. It is an umbrella module that re-exports some stuff from other modules.
2. Michelson types such as key
and signature
may store primitive of any
curve, so we need "union" types in Haskell as well.
During conversion to human-readable representation usually some magical prefix is used. They have been found in source code in some repos (e. g. https://gitlab.com/tezos/tezos/blob/c52ee69231c5ae4d9cec1f3c8aba0c3573922e2a/src/lib_crypto/base58.ml) and checked manually. Existing tests confirm they are correct.
Synopsis
- data PublicKey
- data SecretKey
- data Signature
- data KeyHashTag
- data KeyHash = KeyHash {
- khTag :: KeyHashTag
- khBytes :: ByteString
- detSecretKey :: HasCallStack => ByteString -> SecretKey
- toPublic :: SecretKey -> PublicKey
- signatureToBytes :: ByteArray ba => Signature -> ba
- mkSignature :: ByteArray ba => ba -> Maybe Signature
- parseSignatureRaw :: ByteString -> Either ParseSignatureRawError Signature
- signatureLengthBytes :: HasCallStack => Integral n => n
- checkSignature :: PublicKey -> Signature -> ByteString -> Bool
- data CryptoParseError
- formatPublicKey :: PublicKey -> Text
- mformatPublicKey :: PublicKey -> MText
- parsePublicKey :: Text -> Either CryptoParseError PublicKey
- parsePublicKeyRaw :: ByteString -> Either Text PublicKey
- formatSignature :: Signature -> Text
- mformatSignature :: Signature -> MText
- parseSignature :: Text -> Either CryptoParseError Signature
- formatKeyHash :: KeyHash -> Text
- mformatKeyHash :: KeyHash -> MText
- parseKeyHash :: Text -> Either CryptoParseError KeyHash
- parseKeyHashRaw :: ByteString -> Either CryptoParseError KeyHash
- keyHashLengthBytes :: Integral n => n
- formatSecretKey :: SecretKey -> Text
- parseSecretKey :: Text -> Either CryptoParseError SecretKey
- hashKey :: PublicKey -> KeyHash
- blake2b :: ByteString -> ByteString
- blake2b160 :: ByteString -> ByteString
- sha256 :: ByteString -> ByteString
- sha512 :: ByteString -> ByteString
- encodeBase58Check :: ByteString -> Text
- decodeBase58Check :: Text -> Maybe ByteString
- data B58CheckWithPrefixError
- decodeBase58CheckWithPrefix :: ByteString -> Text -> Either B58CheckWithPrefixError ByteString
- keyDecoders :: [TaggedDecoder PublicKey]
- keyHashDecoders :: [TaggedDecoder KeyHash]
Cryptographic primitive types
Public cryptographic key used by Tezos. There are three cryptographic curves each represented by its own constructor.
PublicKeyEd25519 PublicKey | Public key that uses the ed25519 cryptographic curve. |
PublicKeySecp256k1 PublicKey | Public key that uses the secp256k1 cryptographic curve. |
PublicKeyP256 PublicKey | Public key that uses the NIST P-256 cryptographic curve. |
Instances
Secret cryptographic key used by Tezos.
Constructors correspond to PublicKey
constructors.
SecretKeyEd25519 SecretKey | Secret key that uses the ed25519 cryptographic curve. |
SecretKeySecp256k1 SecretKey | Secret key that uses the secp256k1 cryptographic curve. |
SecretKeyP256 SecretKey | Secret key that uses the NIST P-256 cryptographic curve. |
Instances
Eq SecretKey Source # | |
Show SecretKey Source # | |
Generic SecretKey Source # | |
Arbitrary SecretKey Source # | |
NFData SecretKey Source # | |
Defined in Tezos.Crypto | |
Buildable SecretKey Source # | |
Defined in Tezos.Crypto | |
HasCLReader SecretKey Source # | |
Defined in Tezos.Crypto | |
type Rep SecretKey Source # | |
Defined in Tezos.Crypto type Rep SecretKey = D1 ('MetaData "SecretKey" "Tezos.Crypto" "morley-1.7.0-inplace" 'False) (C1 ('MetaCons "SecretKeyEd25519" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SecretKey)) :+: (C1 ('MetaCons "SecretKeySecp256k1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SecretKey)) :+: C1 ('MetaCons "SecretKeyP256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SecretKey)))) |
Cryptographic signatures used by Tezos.
Constructors correspond to PublicKey
constructors.
Tezos distinguishes signatures for different curves. For instance, ed25519 signatures and secp256k1 signatures are printed differently (have different prefix). However, signatures are packed without information about the curve. For this purpose there is a generic signature which only stores bytes and doesn't carry information about the curve. Apparently unpacking from bytes always produces such signature. Unpacking from string produces a signature with curve information.
SignatureEd25519 Signature | Signature that uses the ed25519 cryptographic curve. |
SignatureSecp256k1 Signature | Siganture that uses the secp256k1 cryptographic curve. |
SignatureP256 Signature | Signature that uses the NIST P-256 cryptographic curve. |
SignatureGeneric ByteString | Generic signature for which curve is unknown. |
Instances
data KeyHashTag Source #
Which curve was used for the hashed public key inside KeyHash
.
Instances
Blake2b_160 hash of a public key.
KeyHash | |
|
Instances
Eq KeyHash Source # | |
Ord KeyHash Source # | |
Show KeyHash Source # | |
Generic KeyHash Source # | |
Arbitrary KeyHash Source # | |
ToJSON KeyHash Source # | |
Defined in Tezos.Crypto | |
FromJSON KeyHash Source # | |
NFData KeyHash Source # | |
Defined in Tezos.Crypto | |
Buildable KeyHash Source # | |
Defined in Tezos.Crypto | |
HasCLReader KeyHash Source # | |
Defined in Tezos.Crypto | |
IsoValue KeyHash Source # | |
TypeHasDoc KeyHash Source # | |
Defined in Michelson.Typed.Haskell.Doc | |
type Rep KeyHash Source # | |
Defined in Tezos.Crypto type Rep KeyHash = D1 ('MetaData "KeyHash" "Tezos.Crypto" "morley-1.7.0-inplace" 'False) (C1 ('MetaCons "KeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "khTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHashTag) :*: S1 ('MetaSel ('Just "khBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))) | |
type ToT KeyHash Source # | |
Defined in Michelson.Typed.Haskell.Value | |
type TypeDocFieldDescriptions KeyHash Source # | |
Defined in Michelson.Typed.Haskell.Doc |
Public/secret key functions
detSecretKey :: HasCallStack => ByteString -> SecretKey Source #
Deterministicaly generate a secret key from seed. Type of the key depends on seed length.
Signature
mkSignature :: ByteArray ba => ba -> Maybe Signature Source #
Make a Signature
from raw bytes.
Can return only generic signature.
parseSignatureRaw :: ByteString -> Either ParseSignatureRawError Signature Source #
signatureLengthBytes :: HasCallStack => Integral n => n Source #
checkSignature :: PublicKey -> Signature -> ByteString -> Bool Source #
Check that a sequence of bytes has been signed with a given key.
Formatting
data CryptoParseError Source #
Error that can happen during parsing of cryptographic primitive types.
CryptoParseWrongBase58Check | |
CryptoParseWrongTag ByteString | |
CryptoParseCryptoError CryptoError | |
CryptoParseUnexpectedLength Builder Int | |
CryptoParseBinaryError Text |
Instances
Eq CryptoParseError Source # | |
Defined in Tezos.Crypto.Util (==) :: CryptoParseError -> CryptoParseError -> Bool # (/=) :: CryptoParseError -> CryptoParseError -> Bool # | |
Show CryptoParseError Source # | |
Defined in Tezos.Crypto.Util showsPrec :: Int -> CryptoParseError -> ShowS # show :: CryptoParseError -> String # showList :: [CryptoParseError] -> ShowS # | |
NFData CryptoParseError Source # | |
Defined in Tezos.Crypto.Util rnf :: CryptoParseError -> () # | |
Buildable CryptoParseError Source # | |
Defined in Tezos.Crypto.Util build :: CryptoParseError -> Builder # |
formatPublicKey :: PublicKey -> Text Source #
mformatPublicKey :: PublicKey -> MText Source #
formatSignature :: Signature -> Text Source #
mformatSignature :: Signature -> MText Source #
formatKeyHash :: KeyHash -> Text Source #
mformatKeyHash :: KeyHash -> MText Source #
keyHashLengthBytes :: Integral n => n Source #
Length of key hash in bytes (only hash itself, no tags, checksums or anything).
formatSecretKey :: SecretKey -> Text Source #
parseSecretKey :: Text -> Either CryptoParseError SecretKey Source #
Parse unencrypted secret key. It accepts formats containing
either with or without the unecrypted
prefix.
Hashing
blake2b :: ByteString -> ByteString Source #
Compute a cryptographic hash of a bytestring using the Blake2b_256 cryptographic hash function. It's used by the BLAKE2B instruction in Michelson.
blake2b160 :: ByteString -> ByteString Source #
Compute a cryptographic hash of a bytestring using the Blake2b_160 cryptographic hash function.
sha256 :: ByteString -> ByteString Source #
Compute a cryptographic hash of a bytestring using the Sha256 cryptographic hash function.
sha512 :: ByteString -> ByteString Source #
Compute a cryptographic hash of a bytestring using the Sha512 cryptographic hash function.
Utilities
encodeBase58Check :: ByteString -> Text Source #
Encode a bytestring in Base58Check format.
decodeBase58Check :: Text -> Maybe ByteString Source #
Decode a bytestring from Base58Check format.
data B58CheckWithPrefixError Source #
Instances
Show B58CheckWithPrefixError Source # | |
Defined in Tezos.Crypto.Util showsPrec :: Int -> B58CheckWithPrefixError -> ShowS # show :: B58CheckWithPrefixError -> String # showList :: [B58CheckWithPrefixError] -> ShowS # |
decodeBase58CheckWithPrefix :: ByteString -> Text -> Either B58CheckWithPrefixError ByteString Source #
Parse a base58check encoded value expecting some prefix. If the actual prefix matches the expected one, it's stripped of and the resulting payload is returned.