{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} module Voting.Protocol.Credential where import Control.DeepSeq (NFData) import Control.Monad (Monad(..), forM_, replicateM) import Data.Bits import Data.Bool import Data.Char (Char) import Data.Either (Either(..), either) import Data.Eq (Eq(..)) import Data.Function (($)) import Data.Functor ((<$>)) import Data.Int (Int) import Data.Maybe (maybe) import Data.Ord (Ord(..)) import Data.Semigroup (Semigroup(..)) import Data.Text (Text) import GHC.Generics (Generic) import Numeric.Natural (Natural) import Prelude (Integral(..), fromIntegral, div) import Text.Show (Show(..)) import qualified Control.Monad.Trans.State.Strict as S import qualified Crypto.KDF.PBKDF2 as Crypto import qualified Data.Aeson as JSON import qualified Data.Aeson.Types as JSON import qualified Data.ByteArray as ByteArray import qualified Data.ByteString as BS import qualified Data.Char as Char import qualified Data.List as List import qualified Data.Text as Text import qualified Data.Text.Encoding as Text import qualified System.Random as Random import Voting.Protocol.FFC -- * Type 'Credential' -- | 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@. newtype Credential = Credential Text deriving (Eq,Show,Generic) deriving newtype NFData deriving newtype JSON.ToJSON instance JSON.FromJSON Credential where parseJSON json@(JSON.String s) = either (\err -> JSON.typeMismatch ("Credential: "<>show err) json) return $ readCredential s parseJSON json = JSON.typeMismatch "Credential" json credentialAlphabet :: [Char] -- TODO: make this an array credentialAlphabet = "123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz" tokenBase :: Int tokenBase = List.length credentialAlphabet tokenLength ::Int tokenLength = 14 -- | @'randomCredential'@ generates a random 'Credential'. randomCredential :: Monad m => Random.RandomGen r => S.StateT r m Credential randomCredential = do rs <- replicateM tokenLength (randomR (fromIntegral tokenBase)) let (tot, cs) = List.foldl' (\(acc,ds) d -> ( acc * tokenBase + d , charOfDigit d : ds ) ) (zero::Int, []) rs let checksum = (neg tot + 53) `mod` 53 -- NOTE: why 53 and not 'tokenBase' ? return $ Credential $ Text.reverse $ Text.pack (charOfDigit checksum:cs) where charOfDigit = (credentialAlphabet List.!!) -- | @'readCredential'@ reads and check the well-formedness of a 'Credential' -- from raw 'Text'. readCredential :: Text -> Either ErrorToken Credential readCredential s | Text.length s /= tokenLength + 1 = Left ErrorToken_Length | otherwise = do tot <- Text.foldl' (\acc c -> acc >>= \a -> ((a * tokenBase) +) <$> digitOfChar c) (Right (zero::Int)) (Text.init s) checksum <- digitOfChar (Text.last s) if (tot + checksum) `mod` 53 == 0 then Right (Credential s) else Left ErrorToken_Checksum where digitOfChar c = maybe (Left $ ErrorToken_BadChar c) Right $ List.elemIndex c credentialAlphabet -- ** Type 'ErrorToken' data ErrorToken = ErrorToken_BadChar Char.Char | ErrorToken_Checksum | ErrorToken_Length deriving (Eq,Show,Generic,NFData) -- ** Type 'UUID' newtype UUID = UUID Text deriving (Eq,Ord,Show,Generic) deriving anyclass (JSON.ToJSON) deriving newtype NFData instance JSON.FromJSON UUID where parseJSON json@(JSON.String s) = either (\err -> JSON.typeMismatch ("UUID: "<>show err) json) return $ readUUID s parseJSON json = JSON.typeMismatch "UUID" json -- | @'randomUUID'@ generates a random 'UUID'. randomUUID :: Monad m => Random.RandomGen r => S.StateT r m UUID randomUUID = do rs <- replicateM tokenLength (randomR (fromIntegral tokenBase)) return $ UUID $ Text.pack $ charOfDigit <$> rs where charOfDigit = (credentialAlphabet List.!!) -- | @'readCredential'@ reads and check the well-formedness of a 'Credential' -- from raw 'Text'. readUUID :: Text -> Either ErrorToken UUID readUUID s | Text.length s /= tokenLength = Left ErrorToken_Length | otherwise = do forM_ (Text.unpack s) digitOfChar return (UUID s) where digitOfChar c = maybe (Left $ ErrorToken_BadChar c) Right $ List.elemIndex c credentialAlphabet -- ** Type 'SecretKey' type SecretKey = E randomSecretKey :: Reifies c FFC => Monad m => RandomGen r => S.StateT r m (SecretKey c) randomSecretKey = random -- | @('credentialSecretKey' uuid cred)@ returns the 'SecretKey' -- derived from given 'uuid' and 'cred' -- using 'Crypto.fastPBKDF2_SHA256'. credentialSecretKey :: Reifies c FFC => UUID -> Credential -> (SecretKey c) credentialSecretKey (UUID uuid) (Credential cred) = fromNatural $ BS.foldl' -- NOTE: interpret the SHA256 as a big-endian number. (\acc b -> acc`shiftL`8 + fromIntegral b) (0::Natural) $ Crypto.fastPBKDF2_SHA256 Crypto.Parameters { Crypto.iterCounts = 1000 , Crypto.outputLength = 32 -- bytes, ie. 256 bits } (Text.encodeUtf8 cred) (Text.encodeUtf8 uuid) -- ** Type 'PublicKey' type PublicKey = G -- | @('publicKey' secKey)@ returns the 'PublicKey' -- derived from given 'SecretKey' @secKey@. publicKey :: Reifies c FFC => SecretKey c -> PublicKey c publicKey = (groupGen ^)