hjugement-protocol-0.0.0.20190513: A cryptographic protocol for the Majority Judgment.

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.Credential

Contents

Synopsis

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
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 #

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" "hjugement-protocol-0.0.0.20190513-FHCeTArdaCC2IRctq0Wzr8" True) (C1 (MetaCons "Credential" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

readCredential :: Text -> Either CredentialError Credential Source #

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

Type CredentialError

data CredentialError Source #

Instances
Eq CredentialError Source # 
Instance details

Defined in Voting.Protocol.Credential

Show CredentialError Source # 
Instance details

Defined in Voting.Protocol.Credential

Generic CredentialError Source # 
Instance details

Defined in Voting.Protocol.Credential

Associated Types

type Rep CredentialError :: Type -> Type #

NFData CredentialError Source # 
Instance details

Defined in Voting.Protocol.Credential

Methods

rnf :: CredentialError -> () #

type Rep CredentialError Source # 
Instance details

Defined in Voting.Protocol.Credential

type Rep CredentialError = D1 (MetaData "CredentialError" "Voting.Protocol.Credential" "hjugement-protocol-0.0.0.20190513-FHCeTArdaCC2IRctq0Wzr8" False) (C1 (MetaCons "CredentialError_BadChar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: (C1 (MetaCons "CredentialError_Checksum" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CredentialError_Length" PrefixI False) (U1 :: Type -> Type)))

Type UUID

newtype UUID Source #

Constructors

UUID Text 
Instances
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 #

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" "hjugement-protocol-0.0.0.20190513-FHCeTArdaCC2IRctq0Wzr8" 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.

Type SecretKey

credentialSecretKey :: SubGroup q => UUID -> Credential -> SecretKey q Source #

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

Type PublicKey

publicKey :: SubGroup q => SecretKey q -> PublicKey q Source #

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