Safe Haskell | None |
---|---|
Language | Haskell2010 |
Voting.Protocol.Credential
Synopsis
- class Key crypto where
- cryptoType :: crypto -> Text
- cryptoName :: crypto -> Text
- randomSecretKey :: Reifies c crypto => Monad m => RandomGen r => StateT r m (SecretKey crypto c)
- credentialSecretKey :: Reifies c crypto => UUID -> Credential -> SecretKey crypto c
- publicKey :: Reifies c crypto => SecretKey crypto c -> PublicKey crypto c
- newtype Credential = Credential Text
- credentialAlphabet :: [Char]
- tokenBase :: Int
- tokenLength :: Int
- randomCredential :: Monad m => RandomGen r => StateT r m Credential
- readCredential :: Text -> Either ErrorToken Credential
- data ErrorToken
- newtype UUID = UUID Text
- randomUUID :: Monad m => RandomGen r => StateT r m UUID
- readUUID :: Text -> Either ErrorToken UUID
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 #
(
returns the credentialSecretKey
uuid cred)SecretKey
derived from given uuid
and cred
using fastPBKDF2_SHA256
.
publicKey :: Reifies c crypto => SecretKey crypto c -> PublicKey crypto c Source #
Instances
Key FFC Source # | |
Defined in Voting.Protocol.FFC Methods cryptoType :: FFC -> Text Source # cryptoName :: FFC -> Text Source # randomSecretKey :: forall c (m :: Type -> Type) r. (Reifies c FFC, Monad m, RandomGen r) => StateT r m (SecretKey FFC c) Source # credentialSecretKey :: Reifies c FFC => UUID -> Credential -> SecretKey FFC c Source # publicKey :: Reifies c FFC => SecretKey FFC c -> PublicKey FFC c Source # |
Type Credential
newtype Credential Source #
A Credential
is a word of (
-characters
from a base alphabet of (tokenLength
+1 ==
15)
characters:
"123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz"
(beware the absence of "0", "O", "I", and "l").
The last character is a checksum.
The entropy is: tokenBase
==
58)(
.tokenLength
* log tokenBase
/ log 2) ==
82.01… bits
Constructors
Credential Text |
Instances
credentialAlphabet :: [Char] Source #
tokenLength :: Int Source #
randomCredential :: Monad m => RandomGen r => StateT r m Credential Source #
generates a random randomCredential
Credential
.
readCredential :: Text -> Either ErrorToken Credential Source #
reads and check the well-formedness of a readCredential
Credential
from raw Text
.
Type ErrorToken
data ErrorToken Source #
Constructors
ErrorToken_BadChar Char | |
ErrorToken_Checksum | |
ErrorToken_Length |
Instances
Eq ErrorToken Source # | |
Defined in Voting.Protocol.Credential | |
Show ErrorToken Source # | |
Defined in Voting.Protocol.Credential Methods showsPrec :: Int -> ErrorToken -> ShowS # show :: ErrorToken -> String # showList :: [ErrorToken] -> ShowS # | |
Generic ErrorToken Source # | |
Defined in Voting.Protocol.Credential Associated Types type Rep ErrorToken :: Type -> Type # | |
NFData ErrorToken Source # | |
Defined in Voting.Protocol.Credential Methods rnf :: ErrorToken -> () # | |
type Rep ErrorToken Source # | |
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
randomUUID :: Monad m => RandomGen r => StateT r m UUID Source #
generates a random randomUUID
UUID
.
readUUID :: Text -> Either ErrorToken UUID Source #
reads and check the well-formedness of a readCredential
Credential
from raw Text
.