morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Tezos.Crypto

Contents

Description

Cryptographic primitives used in Tezos.

Synopsis

Cryptographic primitive types

newtype PublicKey Source #

ED25519 public cryptographic key.

Constructors

PublicKey 
Instances
Eq PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Show PublicKey Source # 
Instance details

Defined in Tezos.Crypto

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

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 #

type ToT PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data SecretKey Source #

ED25519 secret cryptographic key.

Instances
Eq SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Show SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Arbitrary SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Buildable SecretKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: SecretKey -> Builder #

newtype Signature Source #

ED25519 cryptographic signature.

Constructors

Signature 
Instances
Eq Signature Source # 
Instance details

Defined in Tezos.Crypto

Show Signature Source # 
Instance details

Defined in Tezos.Crypto

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

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 #

type ToT Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

newtype KeyHash Source #

b58check of a public key.

Constructors

KeyHash 
Instances
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

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

Buildable KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: KeyHash -> Builder #

IsoValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T Source #

IsoCValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT KeyHash :: CT Source #

ArithOpHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare KeyHash KeyHash :: Type Source #

type ToT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

detSecretKey :: ByteString -> SecretKey Source #

Deterministicaly generate a secret key from seed.

toPublic :: SecretKey -> PublicKey Source #

Create a public key from a secret key.

Formatting

data CryptoParseError Source #

Error that can happen during parsing of cryptographic primitive types.

Signing

sign :: SecretKey -> ByteString -> 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.

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.