morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Tezos.Crypto.P256

Description

P256 cryptographic primitives.

Synopsis

Cryptographic primitive types

newtype PublicKey Source #

P256 public cryptographic key.

Constructors

PublicKey 

Instances

Instances details
Generic PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Associated Types

type Rep PublicKey :: Type -> Type #

Show PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

NFData PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

rnf :: PublicKey -> () #

Buildable PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

build :: PublicKey -> Builder #

Eq PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Ord PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

type Rep PublicKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

type Rep PublicKey = D1 ('MetaData "PublicKey" "Morley.Tezos.Crypto.P256" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "PublicKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPublicKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PublicKey)))

data SecretKey Source #

P256 secret cryptographic key.

Instances

Instances details
Generic SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Associated Types

type Rep SecretKey :: Type -> Type #

Show SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

NFData SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

rnf :: SecretKey -> () #

Buildable SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

build :: SecretKey -> Builder #

Eq SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

type Rep SecretKey Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

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

newtype Signature Source #

P256 cryptographic signature.

Constructors

Signature 

Instances

Instances details
Generic Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Associated Types

type Rep Signature :: Type -> Type #

Show Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

NFData Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

rnf :: Signature -> () #

Buildable Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

build :: Signature -> Builder #

Eq Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

type Rep Signature Source # 
Instance details

Defined in Morley.Tezos.Crypto.P256

type Rep Signature = D1 ('MetaData "Signature" "Morley.Tezos.Crypto.P256" "morley-1.19.0-inplace" '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.

publicKeyLengthBytes :: (Integral n, CheckIntSubType Int n) => n Source #

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

Convert a PublicKey to raw bytes.

signatureLengthBytes :: (Integral n, CheckIntSubType Int n) => n Source #

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.