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

Tezos.Crypto.Secp256k1

Description

Secp256k1 cryptographic primitives.

Synopsis

Cryptographic primitive types

data PublicKey Source #

Secp256k1 public cryptographic key.

Constructors

PublicKey 

Fields

  • unPublicKey :: PublicKey
     
  • pkBytes :: Maybe ByteString

    This is the hack we use to make serialization correct. Decoding is currently not implemented, so when we have to decode bytes we remember these bytes and produce some random public key.

    TODO (#18) remove it.

Instances

Instances details
Eq PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Show PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Generic PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Associated Types

type Rep PublicKey :: Type -> Type #

Arbitrary PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

NFData PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

rnf :: PublicKey -> () #

Buildable PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

build :: PublicKey -> Builder #

type Rep PublicKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

type Rep PublicKey = D1 ('MetaData "PublicKey" "Tezos.Crypto.Secp256k1" "morley-1.2.0-GFTR6HhJxtXGRHqcKAr6TU" 'False) (C1 ('MetaCons "PublicKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPublicKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey) :*: S1 ('MetaSel ('Just "pkBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ByteString))))

data SecretKey Source #

Secp256k1 secret cryptographic key.

Instances

Instances details
Eq SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Show SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Generic SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Associated Types

type Rep SecretKey :: Type -> Type #

Arbitrary SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

NFData SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

rnf :: SecretKey -> () #

type Rep SecretKey Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

type Rep SecretKey = D1 ('MetaData "SecretKey" "Tezos.Crypto.Secp256k1" "morley-1.2.0-GFTR6HhJxtXGRHqcKAr6TU" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSecretKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeyPair)))

newtype Signature Source #

Secp256k1 cryptographic signature.

Constructors

Signature 

Instances

Instances details
Eq Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Show Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Generic Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Associated Types

type Rep Signature :: Type -> Type #

Arbitrary Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

NFData Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

rnf :: Signature -> () #

Buildable Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

build :: Signature -> Builder #

type Rep Signature Source # 
Instance details

Defined in Tezos.Crypto.Secp256k1

type Rep Signature = D1 ('MetaData "Signature" "Tezos.Crypto.Secp256k1" "morley-1.2.0-GFTR6HhJxtXGRHqcKAr6TU" 'True) (C1 ('MetaCons "Signature" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Signature)))

detSecretKey :: ByteString -> SecretKey Source #

Deterministicaly generate a secret key from seed.

toPublic :: SecretKey -> PublicKey Source #

Create a public key from a secret key.

Raw bytes (no checksums, tags or anything)

publicKeyToBytes :: forall ba. ByteArray ba => PublicKey -> ba Source #

Convert a PublicKey to raw bytes.

TODO (#18): apparently it uses compressed SEC format as described in https://www.oreilly.com/library/view/programming-bitcoin/9781492031482/ch04.html However, it is not tested yet.

mkPublicKey :: ByteArrayAccess ba => ba -> Either CryptoParseError PublicKey Source #

Make a PublicKey from raw bytes.

TODO (#18): it should decode from compressed SEC format, but it's left for a future task, so for now we return a constant.

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

Convert a PublicKey to raw bytes.

TODO (#18): apparently a signature always has 64 bytes, so this format might be correct, but it is not tested.

mkSignature :: ByteArray ba => ba -> Either CryptoParseError Signature Source #

Make a Signature from raw bytes.

TODO (#18): apparently a signature always has 64 bytes, so this format might be correct, but it is not tested.

Formatting and parsing

Signing

sign :: MonadRandom m => SecretKey -> ByteString -> m Signature Source #

Sign a message using the secret key.

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

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