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

Morley.Tezos.Crypto.BLS12381

Contents

Description

Support for BLS12-381 elliptic curve.

Some general hints on the implementation can be found in this python re-implementation used by Tezos for testing: https://gitlab.com/metastatedev/tezos/-/commit/f10c39e0030e6b4fdd416a62de7b80b6ffdfeacf#80b4b1585c1e6fa82f2cfaf75001c490613f22c3. And it uses this library inside: https://github.com/ethereum/py_ecc/tree/master/py_ecc/optimized_bls12_381.

Synopsis

Documentation

data Bls12381Fr Source #

An element of an algebraic number field (scalar), used for multiplying Bls12381G1 and Bls12381G2.

Instances

Instances details
Bounded Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Enum Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Num Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Fractional Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Integral Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Real Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Show Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381Fr -> () #

Eq Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Ord Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

HasRPCRepr Bls12381Fr Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381Fr Source #

IsoValue Bls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381Fr :: T Source #

CurveObject Bls12381Fr Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

type AsRPC Bls12381Fr Source # 
Instance details

Defined in Morley.AsRPC

type ToT Bls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

data Bls12381G1 Source #

G1 point on the curve.

Instances

Instances details
Show Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G1 -> () #

Eq Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

HasRPCRepr Bls12381G1 Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381G1 Source #

IsoValue Bls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G1 :: T Source #

CurveObject Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G1 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

type AsRPC Bls12381G1 Source # 
Instance details

Defined in Morley.AsRPC

type ToT Bls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

data Bls12381G2 Source #

G2 point on the curve.

Instances

Instances details
Show Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G2 -> () #

Eq Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

HasRPCRepr Bls12381G2 Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381G2 Source #

IsoValue Bls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G2 :: T Source #

CurveObject Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G2 Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

type AsRPC Bls12381G2 Source # 
Instance details

Defined in Morley.AsRPC

type ToT Bls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

class CurveObject a where Source #

Methods common for all BLS12-381 primitives.

Methods

zero :: a Source #

Representation of 0, aka additive identity.

negate :: a -> a Source #

Negate a value.

add :: a -> a -> a Source #

Add up two values.

generate :: MonadRandom m => m a Source #

Generate a random value.

fromMichelsonBytes :: ByteString -> Either DeserializationError a Source #

Read a value from Michelson's bytes form.

Michelson tends to represent all BLS12-381 types in bytes form, some special types also allow other forms.

toMichelsonBytes :: a -> ByteString Source #

Produce Michelson's bytes representation.

class MultiplyPoint scalar point where Source #

Multiplication operations on BLS12-381 objects.

Methods

multiply :: scalar -> point -> point Source #

Multiply point value by scalar value.

data DeserializationError Source #

All kinds of errors that can occur when reading a Michelson value.

Instances

Instances details
Generic DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Associated Types

type Rep DeserializationError :: Type -> Type #

Show DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: DeserializationError -> () #

Buildable DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Eq DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

RenderDoc DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

type Rep DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

checkPairing :: [(Bls12381G1, Bls12381G2)] -> Bool Source #

Checks that product of pairings of points in the list is equal to 1 in Fq12 field.

Playground

unsafeReadFromHex :: (CurveObject a, HasCallStack) => String -> a Source #

Reads an object from hex string.

To be used only in playground and tests.

generateFrom :: CurveObject a => Int -> a Source #

Generate a random value from given seed.

g2One :: Bls12381G2 Source #

1 represented in G2.