secret-sharing-1.0.1.1: Information-theoretic secure secret sharing

CopyrightPeter Robinson 2014
LicenseLGPL
MaintainerPeter Robinson <peter.robinson@monoid.at>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Crypto.SecretSharing.Internal

Description

 
Synopsis

Documentation

polyInterp :: Fractional a => [(a, a)] -> a -> a Source #

Evaluate a Lagrange interpolation polynomial passing through the specified set of points.

slidingFocus :: [a] -> [([a], a, [a])] Source #

data ByteShare Source #

A share of an encoded byte.

Constructors

ByteShare 

Fields

Instances
Eq ByteShare Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Show ByteShare Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Generic ByteShare Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Associated Types

type Rep ByteShare :: Type -> Type #

Binary ByteShare Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

type Rep ByteShare Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

type Rep ByteShare = D1 (MetaData "ByteShare" "Crypto.SecretSharing.Internal" "secret-sharing-1.0.1.1-K3DC0AFtIH45LR2JRnUpVD" False) (C1 (MetaCons "ByteShare" PrefixI True) (S1 (MetaSel (Just "shareId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "reconstructionThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "shareValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

data Share Source #

A share of the encoded secret.

Constructors

Share 

Fields

Instances
Eq Share Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Methods

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

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

Show Share Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Methods

showsPrec :: Int -> Share -> ShowS #

show :: Share -> String #

showList :: [Share] -> ShowS #

Generic Share Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Associated Types

type Rep Share :: Type -> Type #

Methods

from :: Share -> Rep Share x #

to :: Rep Share x -> Share #

Binary Share Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Methods

put :: Share -> Put #

get :: Get Share #

putList :: [Share] -> Put #

type Rep Share Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

type Rep Share = D1 (MetaData "Share" "Crypto.SecretSharing.Internal" "secret-sharing-1.0.1.1-K3DC0AFtIH45LR2JRnUpVD" False) (C1 (MetaCons "Share" PrefixI True) (S1 (MetaSel (Just "theShare") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ByteShare])))

encode Source #

Arguments

:: Int

m

-> Int

n

-> ByteString

the secret that we want to share

-> IO [Share] 

Encodes a ByteString as a list of n shares, m of which are required for reconstruction. Lives in the IO to access a random source.

decode Source #

Arguments

:: [Share]

list of at least m shares

-> ByteString

reconstructed secret

Reconstructs a (secret) bytestring from a list of (at least m) shares. Throws AssertionFailed if the number of shares is too small.

groupInto :: Int -> [a] -> [[a]] Source #

Groups a list into blocks of certain size. Running time: O(n)

newtype FField Source #

A finite prime field. All computations are performed in this field.

Constructors

FField 

Fields

Instances
Eq FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Methods

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

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

Fractional FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Num FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Ord FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Read FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Show FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Generic FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

Associated Types

type Rep FField :: Type -> Type #

Methods

from :: FField -> Rep FField x #

to :: Rep FField x -> FField #

FiniteField FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

type Rep FField Source # 
Instance details

Defined in Crypto.SecretSharing.Internal

type Rep FField = D1 (MetaData "FField" "Crypto.SecretSharing.Internal" "secret-sharing-1.0.1.1-K3DC0AFtIH45LR2JRnUpVD" True) (C1 (MetaCons "FField" PrefixI True) (S1 (MetaSel (Just "number") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PrimeField 1021))))

prime :: Int Source #

The size of the finite field

type Polyn = [FField] Source #

A polynomial over the finite field given as a list of coefficients.

evalPolynomial :: Polyn -> FField -> FField Source #

Evaluates the polynomial at a given point.