-- PVP: +-+------- breaking API changes
-- | | +----- non-breaking API additions
-- | | | +--- code changes with no API change
-version: 0.0.0.20190519
+version: 0.0.1.20190623
category: Politic
synopsis: A cryptographic protocol for the Majority Judgment.
description:
-- using 'Crypto.fastPBKDF2_SHA256'.
credentialSecretKey :: Reifies c FFC => UUID -> Credential -> (SecretKey c)
credentialSecretKey (UUID uuid) (Credential cred) =
- fromNatural $ BS.foldl'
- (\acc b -> acc`shiftL`3 + fromIntegral b)
- (0::Natural)
- (ByteArray.convert deriv)
- where
- deriv :: BS.ByteString
- deriv =
- Crypto.fastPBKDF2_SHA256
- Crypto.Parameters
- { Crypto.iterCounts = 1000
- , Crypto.outputLength = 256 `div` 8
- }
- (Text.encodeUtf8 cred)
- (Text.encodeUtf8 uuid)
+ 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
hash :: Reifies c FFC => BS.ByteString -> [G c] -> E c
hash bs gs = do
let s = bs <> BS.intercalate (fromString ",") (bytesNat <$> gs)
- let h = ByteArray.convert (Crypto.hashWith Crypto.SHA256 s)
- fromNatural (BS.foldl' (\acc b -> acc`shiftL`3 + fromIntegral b) (0::Natural) h)
+ let h = Crypto.hashWith Crypto.SHA256 s
+ fromNatural $
+ BS.foldl' -- NOTE: interpret the SHA256 as a big-endian number.
+ (\acc b -> acc`shiftL`8 + fromIntegral b)
+ (0::Natural)
+ (ByteArray.convert h)
-- * Type 'E'
-- | An exponent of a (necessarily cyclic) subgroup of a Finite Prime Field.
{-# LANGUAGE OverloadedStrings #-}
module HUnit.Credential where
-import Control.Applicative (Applicative(..))
import Test.Tasty.HUnit
import qualified Control.Monad.Trans.State.Strict as S
import qualified System.Random as Random
, "xLcs7ev6Jy6FHHE" ==> Right (Credential "xLcs7ev6Jy6FHHE")
]
, testGroup "credentialSecretKey" $
- [ testSecretKey weakFFC 0 122
- , testSecretKey weakFFC 1 35
- , testSecretKey beleniosFFC 0 2317630607062989137269685509390
- , testSecretKey beleniosFFC 1 1968146140481358915910346867611
+ [ testSecretKey beleniosFFC
+ (UUID "xLcs7ev6Jy6FHH")
+ (Credential "xLcs7ev6Jy6FHHE")
+ 24202898752499029126606335829564687069186982035759723128887013101942425902424
]
]
-testSecretKey :: FFC -> Int -> Natural -> TestTree
-testSecretKey ffc seed exp =
+testSecretKey :: FFC -> UUID -> Credential -> Natural -> TestTree
+testSecretKey ffc uuid cred exp =
reify ffc $ \(Proxy::Proxy c) ->
- let (uuid@(UUID u), cred@(Credential c)) =
- (`S.evalState` Random.mkStdGen seed) $
- (,) <$> randomUUID <*> randomCredential in
- testCase (show (u,c)) $
+ testCase (show (uuid,cred)) $
credentialSecretKey @c uuid cred @?= E exp
reify weakFFC $ \(Proxy::Proxy c) ->
[ testCase "[groupGen]" $
hash "start" [groupGen @c] @?=
- fromNatural 100
+ fromNatural 62
, testCase "[groupGen, groupGen]" $
hash "start" [groupGen @c, groupGen] @?=
- fromNatural 16
+ fromNatural 31
]
, testGroup "BeleniosParams" $
reify beleniosFFC $ \(Proxy::Proxy c) ->
[ testCase "[groupGen]" $
hash "start" [groupGen @c] @?=
- fromNatural 1832875488615060263192702367259
+ fromNatural 75778590284190557660612328423573274641033882642784670156837892421285248292707
, testCase "[groupGen, groupGen]" $
hash "start" [groupGen @c, groupGen] @?=
- fromNatural 2495277906542783643199702546512
+ fromNatural 28798937720387703653439047952832768487958170248947132321730024269734141660223
]
]
]