lib: doc: add TODOs
[majurity.git] / hjugement-protocol / tests / HUnit / Credential.hs
index 0b63b55416d9d7becb7bcfc863ad2b3cec3e6db9..08ccbb51bb4111b1dad411d26ebbc2fca97a62a8 100644 (file)
@@ -1,18 +1,15 @@
-{-# LANGUAGE AllowAmbiguousTypes #-}
 {-# 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
 
-import Protocol.Arithmetic
-import Protocol.Credential
+import Voting.Protocol
 import Utils
 
-hunit :: TestTree
-hunit = testGroup "Credential"
+hunit :: Reifies v Version => Proxy v -> TestTree
+hunit _v = testGroup "Credential"
  [ testGroup "randomCredential"
         [ testCase "0" $
                S.evalState randomCredential (Random.mkStdGen 0) @?=
@@ -26,29 +23,29 @@ hunit = testGroup "Credential"
  , testGroup "readCredential" $
                let (==>) inp exp =
                        testCase (show inp) $ readCredential inp @?= exp in
-        [ "" ==> Left CredentialError_Length
-        , "xLcs7ev6Jy6FH_E"  ==> Left (CredentialError_BadChar '_')
-        , "xLcs7ev6Jy6FHIE"  ==> Left (CredentialError_BadChar 'I')
-        , "xLcs7ev6Jy6FH0E"  ==> Left (CredentialError_BadChar '0')
-        , "xLcs7ev6Jy6FHOE"  ==> Left (CredentialError_BadChar 'O')
-        , "xLcs7ev6Jy6FHlE"  ==> Left (CredentialError_BadChar 'l')
-        , "xLcs7ev6Jy6FH6"   ==> Left CredentialError_Length
-        , "xLcs7ev6Jy6FHHy1" ==> Left CredentialError_Length
-        , "xLcs7ev6Jy6FHHF"  ==> Left CredentialError_Checksum
+        [ "" ==> Left ErrorToken_Length
+        , "xLcs7ev6Jy6FH_E"  ==> Left (ErrorToken_BadChar '_')
+        , "xLcs7ev6Jy6FHIE"  ==> Left (ErrorToken_BadChar 'I')
+        , "xLcs7ev6Jy6FH0E"  ==> Left (ErrorToken_BadChar '0')
+        , "xLcs7ev6Jy6FHOE"  ==> Left (ErrorToken_BadChar 'O')
+        , "xLcs7ev6Jy6FHlE"  ==> Left (ErrorToken_BadChar 'l')
+        , "xLcs7ev6Jy6FH6"   ==> Left ErrorToken_Length
+        , "xLcs7ev6Jy6FHHy1" ==> Left ErrorToken_Length
+        , "xLcs7ev6Jy6FHHF"  ==> Left ErrorToken_Checksum
         , "xLcs7ev6Jy6FHHE"  ==> Right (Credential "xLcs7ev6Jy6FHHE")
         ]
  , testGroup "credentialSecretKey" $
-        [ testSecretKey @WeakParams 0 $ E (F 122)
-        , testSecretKey @WeakParams 1 $ E (F 35)
-        , testSecretKey @BeleniosParams 0 $ E (F 2317630607062989137269685509390)
-        , testSecretKey @BeleniosParams 1 $ E (F 1968146140481358915910346867611)
+        [  testSecretKey beleniosFFC
+                (UUID "xLcs7ev6Jy6FHH")
+                (Credential "xLcs7ev6Jy6FHHE")
+                24202898752499029126606335829564687069186982035759723128887013101942425902424
         ]
  ]
 
-testSecretKey :: forall q. SubGroup q => Int -> E q -> TestTree
-testSecretKey seed exp =
-       let (uuid@(UUID u), cred@(Credential c)) =
-               (`S.evalState` Random.mkStdGen seed) $
-                       (,) <$> randomUUID <*> randomCredential in
-       testCase (show (u,c)) $
-               credentialSecretKey @q uuid cred @?= exp
+testSecretKey ::
+ ReifyCrypto crypto => Key crypto =>
+ crypto -> UUID -> Credential -> Natural -> TestTree
+testSecretKey crypto uuid cred exp =
+       reifyCrypto crypto $ \(_c::Proxy c) ->
+               testCase (show (uuid,cred)) $
+                       credentialSecretKey @_ @c uuid cred @?= E exp