majurity-protocol-0.0.10.20191104: A cryptographic protocol for the Majority Judgment.
Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.Credential

Synopsis

Class Key

class Key crypto where Source #

Methods

cryptoType :: crypto -> Text Source #

Type of cryptography, eg. FFC.

cryptoName :: crypto -> Text Source #

Name of the cryptographic paramaters, eg. Belenios.

randomSecretKey :: Reifies c crypto => Monad m => RandomGen r => StateT r m (SecretKey crypto c) Source #

Generate a random SecretKey.

credentialSecretKey :: Reifies c crypto => UUID -> Credential -> SecretKey crypto c Source #

(credentialSecretKey uuid cred) returns the SecretKey derived from given uuid and cred using fastPBKDF2_SHA256.

publicKey :: Reifies c crypto => SecretKey crypto c -> PublicKey crypto c Source #

(publicKey secKey) returns the PublicKey derived from given SecretKey secKey.

Instances

Instances details
Key FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Type Credential

newtype Credential Source #

A Credential is a word of (tokenLength+1 == 15)-characters from a base alphabet of (tokenBase == 58) characters: "123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz" (beware the absence of "0", "O", "I", and "l"). The last character is a checksum. The entropy is: (tokenLength * log tokenBase / log 2) == 82.01… bits.

Constructors

Credential Text 

Instances

Instances details
Eq Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

Show Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

Generic Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

Associated Types

type Rep Credential :: Type -> Type #

ToJSON Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

FromJSON Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

NFData Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

rnf :: Credential -> () #

type Rep Credential Source # 
Instance details

Defined in Voting.Protocol.Credential

type Rep Credential = D1 ('MetaData "Credential" "Voting.Protocol.Credential" "majurity-protocol-0.0.10.20191104-inplace" 'True) (C1 ('MetaCons "Credential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

readCredential :: Text -> Either ErrorToken Credential Source #

readCredential reads and check the well-formedness of a Credential from raw Text.

Type ErrorToken

data ErrorToken Source #

Instances

Instances details
Eq ErrorToken Source # 
Instance details

Defined in Voting.Protocol.Credential

Show ErrorToken Source # 
Instance details

Defined in Voting.Protocol.Credential

Generic ErrorToken Source # 
Instance details

Defined in Voting.Protocol.Credential

Associated Types

type Rep ErrorToken :: Type -> Type #

NFData ErrorToken Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

rnf :: ErrorToken -> () #

type Rep ErrorToken Source # 
Instance details

Defined in Voting.Protocol.Credential

type Rep ErrorToken = D1 ('MetaData "ErrorToken" "Voting.Protocol.Credential" "majurity-protocol-0.0.10.20191104-inplace" 'False) (C1 ('MetaCons "ErrorToken_BadChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: (C1 ('MetaCons "ErrorToken_Checksum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorToken_Length" 'PrefixI 'False) (U1 :: Type -> Type)))

Type UUID

newtype UUID Source #

Constructors

UUID Text 

Instances

Instances details
Eq UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

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

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

Ord UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Show UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Generic UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

Associated Types

type Rep UUID :: Type -> Type #

Methods

from :: UUID -> Rep UUID x #

to :: Rep UUID x -> UUID #

ToJSON UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

FromJSON UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

NFData UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

rnf :: UUID -> () #

type Rep UUID Source # 
Instance details

Defined in Voting.Protocol.Credential

type Rep UUID = D1 ('MetaData "UUID" "Voting.Protocol.Credential" "majurity-protocol-0.0.10.20191104-inplace" 'True) (C1 ('MetaCons "UUID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

randomUUID :: Monad m => RandomGen r => StateT r m UUID Source #

randomUUID generates a random UUID.

readUUID :: Text -> Either ErrorToken UUID Source #

readCredential reads and check the well-formedness of a Credential from raw Text.