morley-1.7.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Tezos.Crypto

Description

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

Cryptographic primitive types

data PublicKey Source #

Public cryptographic key used by Tezos. There are three cryptographic curves each represented by its own constructor.

Constructors

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

Instances details
Eq PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Show PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Generic PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep PublicKey :: Type -> Type #

Arbitrary PublicKey Source # 
Instance details

Defined in Tezos.Crypto

ToJSON PublicKey Source # 
Instance details

Defined in Tezos.Crypto

FromJSON PublicKey Source # 
Instance details

Defined in Tezos.Crypto

NFData PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: PublicKey -> () #

Buildable PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: PublicKey -> Builder #

IsoValue PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T Source #

TypeHasDoc PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep PublicKey Source # 
Instance details

Defined in Tezos.Crypto

type ToT PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

data SecretKey Source #

Secret cryptographic key used by Tezos. Constructors correspond to PublicKey constructors.

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

Instances details
Eq SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Show SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Generic SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep SecretKey :: Type -> Type #

Arbitrary SecretKey Source # 
Instance details

Defined in Tezos.Crypto

NFData SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: SecretKey -> () #

Buildable SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: SecretKey -> Builder #

HasCLReader SecretKey Source # 
Instance details

Defined in Tezos.Crypto

type Rep SecretKey Source # 
Instance details

Defined in Tezos.Crypto

data Signature Source #

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.

Constructors

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

Instances details
Eq Signature Source # 
Instance details

Defined in Tezos.Crypto

Show Signature Source # 
Instance details

Defined in Tezos.Crypto

Generic Signature Source # 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep Signature :: Type -> Type #

Arbitrary Signature Source # 
Instance details

Defined in Tezos.Crypto

ToJSON Signature Source # 
Instance details

Defined in Tezos.Crypto

FromJSON Signature Source # 
Instance details

Defined in Tezos.Crypto

NFData Signature Source # 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: Signature -> () #

Buildable Signature Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: Signature -> Builder #

IsoValue Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T Source #

TypeHasDoc Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep Signature Source # 
Instance details

Defined in Tezos.Crypto

type ToT Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

data KeyHashTag Source #

Which curve was used for the hashed public key inside KeyHash.

Instances

Instances details
Bounded KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Enum KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Eq KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Ord KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Show KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Generic KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep KeyHashTag :: Type -> Type #

Arbitrary KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

NFData KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: KeyHashTag -> () #

type Rep KeyHashTag Source # 
Instance details

Defined in Tezos.Crypto

type Rep KeyHashTag = D1 ('MetaData "KeyHashTag" "Tezos.Crypto" "morley-1.7.0-inplace" 'False) (C1 ('MetaCons "KeyHashEd25519" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KeyHashSecp256k1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyHashP256" 'PrefixI 'False) (U1 :: Type -> Type)))

data KeyHash Source #

Blake2b_160 hash of a public key.

Constructors

KeyHash 

Fields

Instances

Instances details
Eq KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

(==) :: KeyHash -> KeyHash -> Bool #

(/=) :: KeyHash -> KeyHash -> Bool #

Ord KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Show KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Generic KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep KeyHash :: Type -> Type #

Methods

from :: KeyHash -> Rep KeyHash x #

to :: Rep KeyHash x -> KeyHash #

Arbitrary KeyHash Source # 
Instance details

Defined in Tezos.Crypto

ToJSON KeyHash Source # 
Instance details

Defined in Tezos.Crypto

FromJSON KeyHash Source # 
Instance details

Defined in Tezos.Crypto

NFData KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: KeyHash -> () #

Buildable KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: KeyHash -> Builder #

HasCLReader KeyHash Source # 
Instance details

Defined in Tezos.Crypto

IsoValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T Source #

TypeHasDoc KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type Rep KeyHash Source # 
Instance details

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 # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type TypeDocFieldDescriptions KeyHash Source # 
Instance details

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.

toPublic :: SecretKey -> PublicKey Source #

Create a public key from a secret key.

Signature

signatureToBytes :: ByteArray ba => Signature -> ba Source #

Convert a Signature to raw bytes.

mkSignature :: ByteArray ba => ba -> Maybe Signature Source #

Make a Signature from raw bytes. Can return only generic signature.

parseSignatureRaw :: ByteString -> Either ParseSignatureRawError Signature Source #

checkSignature :: PublicKey -> Signature -> ByteString -> Bool Source #

Check that a sequence of bytes has been signed with a given key.

Formatting

keyHashLengthBytes :: Integral n => n Source #

Length of key hash in bytes (only hash itself, no tags, checksums or anything).

parseSecretKey :: Text -> Either CryptoParseError SecretKey Source #

Parse unencrypted secret key. It accepts formats containing either with or without the unecrypted prefix.

Hashing

hashKey :: PublicKey -> KeyHash Source #

Compute the b58check of a public key hash.

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.

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.