web: continue to purescriptify Cryptography
[majurity.git] / hjugement-protocol / src / Voting / Protocol / Trustee / Indispensable.hs
index 3c26f981ad56f7f130245f1b82127fb6e751a68c..58bde8d43a7a8c77506f1a242a05e5f4f88c7d10 100644 (file)
@@ -7,7 +7,7 @@ module Voting.Protocol.Trustee.Indispensable where
 import Control.DeepSeq (NFData)
 import Control.Monad (Monad(..), foldM, unless)
 import Control.Monad.Trans.Except (ExceptT(..), throwE)
-import Data.Aeson (ToJSON(..),FromJSON(..),(.:),(.=))
+import Data.Aeson (ToJSON(..), FromJSON(..), (.:), (.=))
 import Data.Eq (Eq(..))
 import Data.Function (($))
 import Data.Functor ((<$>))
@@ -24,9 +24,10 @@ import qualified Data.ByteString as BS
 import qualified Data.List as List
 
 import Voting.Protocol.Utils
-import Voting.Protocol.Arith
+import Voting.Protocol.Arithmetic
+import Voting.Protocol.Version
+import Voting.Protocol.Cryptography
 import Voting.Protocol.Credential
-import Voting.Protocol.Election
 import Voting.Protocol.Tally
 
 -- * Type 'TrusteePublicKey'
@@ -51,7 +52,7 @@ deriving instance Eq (G crypto c) => Eq (TrusteePublicKey crypto v c)
 deriving instance (Show (G crypto c), Show (PublicKey crypto c)) => Show (TrusteePublicKey crypto v c)
 deriving instance NFData (G crypto c) => NFData (TrusteePublicKey crypto v c)
 instance
- ( Group crypto
+ ( Reifies v Version
  , ToJSON (G crypto c)
  ) => ToJSON (TrusteePublicKey crypto v c) where
        toJSON TrusteePublicKey{..} =
@@ -65,9 +66,8 @@ instance
                 <> "public_key" .= trustee_PublicKey
                 )
 instance
- ( Reifies c crypto
- , Group crypto
- , FromJSON (PublicKey crypto c)
+ ( Reifies v Version
+ , CryptoParams crypto c
  ) => FromJSON (TrusteePublicKey crypto v c) where
        parseJSON = JSON.withObject "TrusteePublicKey" $ \o -> do
                trustee_PublicKey <- o .: "public_key"
@@ -81,12 +81,8 @@ instance
 -- and a 'Proof' of its knowledge.
 proveIndispensableTrusteePublicKey ::
  Reifies v Version =>
- Reifies c crypto =>
- Group crypto =>
+ CryptoParams crypto c =>
  Key crypto =>
- Multiplicative (G crypto c) =>
- Invertible (G crypto c) =>
- ToNatural (G crypto c) =>
  Monad m => RandomGen r =>
  SecretKey crypto c -> S.StateT r m (TrusteePublicKey crypto v c)
 proveIndispensableTrusteePublicKey trustSecKey = do
@@ -104,11 +100,7 @@ proveIndispensableTrusteePublicKey trustSecKey = do
 -- the given 'trustee_PublicKey' is known by the trustee.
 verifyIndispensableTrusteePublicKey ::
  Reifies v Version =>
- Reifies c crypto =>
- Group crypto =>
- Multiplicative (G crypto c) =>
- Invertible (G crypto c) =>
- ToNatural (G crypto c) =>
+ CryptoParams crypto c =>
  Monad m =>
  TrusteePublicKey crypto v c ->
  ExceptT ErrorTrusteePublicKey m ()
@@ -128,8 +120,7 @@ data ErrorTrusteePublicKey
 
 -- ** Hashing
 indispensableTrusteePublicKeyStatement ::
- Reifies c crypto =>
- ToNatural (G crypto c) =>
+ CryptoParams crypto c =>
  PublicKey crypto c -> BS.ByteString
 indispensableTrusteePublicKeyStatement trustPubKey =
        "pok|"<>bytesNat trustPubKey<>"|"
@@ -139,10 +130,7 @@ indispensableTrusteePublicKeyStatement trustPubKey =
 -- ** Generating an 'Election''s 'PublicKey' from multiple 'TrusteePublicKey's.
 
 combineIndispensableTrusteePublicKeys ::
- Reifies c crypto =>
- Multiplicative (G crypto c) =>
- Invertible (G crypto c) =>
- ToNatural (G crypto c) =>
+ CryptoParams crypto c =>
  [TrusteePublicKey crypto v c] -> PublicKey crypto c
 combineIndispensableTrusteePublicKeys =
        List.foldr (\TrusteePublicKey{..} -> (trustee_PublicKey *)) one
@@ -151,11 +139,7 @@ combineIndispensableTrusteePublicKeys =
 
 verifyIndispensableDecryptionShareByTrustee ::
  Reifies v Version =>
- Reifies c crypto =>
- Group crypto =>
- Multiplicative (G crypto c) =>
- Invertible (G crypto c) =>
- ToNatural (G crypto c) =>
+ CryptoParams crypto c =>
  Monad m =>
  EncryptedTally crypto v c -> [PublicKey crypto c] -> [DecryptionShare crypto v c] ->
  ExceptT ErrorTally m ()
@@ -169,11 +153,7 @@ verifyIndispensableDecryptionShareByTrustee encByChoiceByQuest =
 -- returns the 'DecryptionFactor's by choice by 'Question'
 combineIndispensableDecryptionShares ::
  Reifies v Version =>
- Reifies c crypto =>
- Group crypto =>
- Multiplicative (G crypto c) =>
- Invertible (G crypto c) =>
- ToNatural (G crypto c) =>
+ CryptoParams crypto c =>
  [PublicKey crypto c] -> DecryptionShareCombinator crypto v c
 combineIndispensableDecryptionShares
  pubKeyByTrustee