pvss-0.2.0: Public Verifiable Secret Sharing

Safe HaskellNone
LanguageHaskell2010

Crypto.PVSS

Contents

Synopsis

Simple alias

type Threshold = Integer Source #

The number of shares needed to reconstitute the secret

Threshold need to be a strictly positive, and less or equal to number of participants given N the number of participants, this should hold: 1 <= t <= N

type ShareId = Integer Source #

The ID associated with a share

data Point Source #

Instances

Eq Point Source # 

Methods

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

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

Show Point Source # 

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Generic Point Source # 

Associated Types

type Rep Point :: * -> * #

Methods

from :: Point -> Rep Point x #

to :: Rep Point x -> Point #

Binary Point Source # 

Methods

put :: Point -> Put #

get :: Get Point #

putList :: [Point] -> Put #

NFData Point Source # 

Methods

rnf :: Point -> () #

type Rep Point Source # 
type Rep Point = D1 (MetaData "Point" "Crypto.PVSS.ECC" "pvss-0.2.0-44yZEAS3v5K3yAPZSxB9tG" True) (C1 (MetaCons "Point" PrefixI True) (S1 (MetaSel (Just Symbol "unPoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EcPoint)))

data Proof Source #

The generated proof

Instances

Eq Proof Source # 

Methods

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

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

Show Proof Source # 

Methods

showsPrec :: Int -> Proof -> ShowS #

show :: Proof -> String #

showList :: [Proof] -> ShowS #

Generic Proof Source # 

Associated Types

type Rep Proof :: * -> * #

Methods

from :: Proof -> Rep Proof x #

to :: Rep Proof x -> Proof #

Binary Proof Source # 

Methods

put :: Proof -> Put #

get :: Get Proof #

putList :: [Proof] -> Put #

NFData Proof Source # 

Methods

rnf :: Proof -> () #

type Rep Proof Source # 
type Rep Proof

data Scalar Source #

Instances

Eq Scalar Source # 

Methods

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

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

Show Scalar Source # 
Generic Scalar Source # 

Associated Types

type Rep Scalar :: * -> * #

Methods

from :: Scalar -> Rep Scalar x #

to :: Rep Scalar x -> Scalar #

Binary Scalar Source # 

Methods

put :: Scalar -> Put #

get :: Get Scalar #

putList :: [Scalar] -> Put #

NFData Scalar Source # 

Methods

rnf :: Scalar -> () #

type Rep Scalar Source # 
type Rep Scalar = D1 (MetaData "Scalar" "Crypto.PVSS.ECC" "pvss-0.2.0-44yZEAS3v5K3yAPZSxB9tG" True) (C1 (MetaCons "Scalar" PrefixI True) (S1 (MetaSel (Just Symbol "unScalar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

data Secret Source #

Secret

Instances

data KeyPair Source #

Instances

Eq KeyPair Source # 

Methods

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

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

Show KeyPair Source # 
Generic KeyPair Source # 

Associated Types

type Rep KeyPair :: * -> * #

Methods

from :: KeyPair -> Rep KeyPair x #

to :: Rep KeyPair x -> KeyPair #

Binary KeyPair Source # 

Methods

put :: KeyPair -> Put #

get :: Get KeyPair #

putList :: [KeyPair] -> Put #

NFData KeyPair Source # 

Methods

rnf :: KeyPair -> () #

type Rep KeyPair Source # 
type Rep KeyPair = D1 (MetaData "KeyPair" "Crypto.PVSS.ECC" "pvss-0.2.0-44yZEAS3v5K3yAPZSxB9tG" False) (C1 (MetaCons "KeyPair" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "toPrivateKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrivateKey)) (S1 (MetaSel (Just Symbol "toPublicKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PublicKey))))

Types

data Escrow Source #

Constructors

Escrow 

Instances

Eq Escrow Source # 

Methods

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

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

Show Escrow Source # 
Generic Escrow Source # 

Associated Types

type Rep Escrow :: * -> * #

Methods

from :: Escrow -> Rep Escrow x #

to :: Rep Escrow x -> Escrow #

NFData Escrow Source # 

Methods

rnf :: Escrow -> () #

type Rep Escrow Source # 
type Rep Escrow

data EncryptedShare Source #

An encrypted share associated to a party's key.

Constructors

EncryptedShare 

Fields

data DecryptedShare Source #

An decrypted share decrypted by a party's key and

Constructors

DecryptedShare 

Fields

method

escrow Source #

Arguments

:: MonadRandom randomly 
=> Threshold

PVSS scheme configuration n/t threshold

-> [PublicKey]

Participants public keys

-> randomly (ExtraGen, Secret, Proof, [Commitment], [EncryptedShare]) 

Prepare a secret into public encrypted shares for distributions using the PVSS scheme

returns: * the encrypted secret which is locked symmetrically to the DH-secret (g^random) * the list of public commitments (Cj) to the scheme * The encrypted shares that should be distributed to each partipants.

escrowWith Source #

Arguments

:: MonadRandom randomly 
=> Escrow 
-> [PublicKey]

Participants public keys

-> randomly ([Commitment], [EncryptedShare]) 

Escrow with a given polynomial

escrowNew :: MonadRandom randomly => Threshold -> randomly Escrow Source #

Prepare a new escrowing context

The only needed parameter is the threshold do not re-use an escrow context for different context.

createCommitments :: Escrow -> [Commitment] Source #

Create all the commitments

there is threshold commitments in the list

sharesCreate :: MonadRandom randomly => Escrow -> [Commitment] -> [PublicKey] -> randomly [EncryptedShare] Source #

Create all the encrypted share associated with specific public key

shareCreate :: MonadRandom randomly => Escrow -> [Commitment] -> ShareId -> PublicKey -> randomly EncryptedShare Source #

Create a specific share given a public key and the overall parameters

shareDecrypt :: MonadRandom randomly => KeyPair -> EncryptedShare -> randomly DecryptedShare Source #

Decrypt an Encrypted share using the party's key pair. Doesn't verify if an encrypted share is valid, for this you need to use verifyEncryptedShare

1) compute Si = Yi ^ (1/xi) = G^(p(i)) 2) create a proof of the valid decryption

verifyEncryptedShare Source #

Arguments

:: ExtraGen 
-> [Commitment] 
-> (EncryptedShare, PublicKey)

the encrypted and the associated public key

-> Bool 

Verify an encrypted share

anyone can do that given the extra generator and the commitments

verifyDecryptedShare :: (EncryptedShare, PublicKey, DecryptedShare) -> Bool Source #

Verify a decrypted share against the public key and the encrypted share

verifySecret :: ExtraGen -> [Commitment] -> Secret -> Proof -> Bool Source #

Verify that a secret recovered is the one escrow

getValidRecoveryShares :: Threshold -> [(EncryptedShare, PublicKey, DecryptedShare)] -> [DecryptedShare] Source #

Get #Threshold decrypted share that are deemed valid

recover :: [DecryptedShare] -> Secret Source #

Recover the DhSecret used

Need to pass the correct amount of shares (# threshold), preferably from a getValidRecoveryShares call

secretToDhSecret :: Secret -> DhSecret Source #

Transform a secret into a usable random value

temporary export to get testing

keyPairGenerate :: MonadRandom randomly => randomly KeyPair Source #