]> Git — Sourcephile - majurity.git/blob - hjugement-cli/src/Hjugement/CLI/Trustee.hs
protocol: add CLI.Voter
[majurity.git] / hjugement-cli / src / Hjugement / CLI / Trustee.hs
1 {-# LANGUAGE NoMonomorphismRestriction #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE StrictData #-}
4 {-# OPTIONS_GHC -Wno-missing-signatures #-}
5 module Hjugement.CLI.Trustee where
6
7 import Control.Applicative (Applicative(..))
8 import Control.Monad (Monad(..), forM, forM_, join, void)
9 import Control.Monad.Trans.Class (MonadTrans(..))
10 import Control.Monad.Trans.Maybe (MaybeT(..))
11 import Control.Monad.Trans.State.Strict (runState, runStateT)
12 import Data.Bits (setBit)
13 import Data.Bool
14 import Data.ByteString (ByteString)
15 import Data.Either (Either(..))
16 import Data.Eq (Eq(..))
17 import Data.Foldable (Foldable, foldMap, length, null)
18 import Data.Function (($), (.), id, flip)
19 import Data.Functor ((<$>))
20 import Data.Int (Int)
21 import Data.Maybe (Maybe(..), maybe, fromMaybe)
22 import Data.Monoid (Monoid(..))
23 import Data.Ord (Ord(..))
24 import Data.Proxy (Proxy(..))
25 import Data.Semigroup (Semigroup(..))
26 import Data.String (String)
27 import Data.Text (Text)
28 import GHC.Natural (minusNatural, minusNaturalMaybe)
29 import GHC.Prim (coerce)
30 import Numeric.Natural (Natural)
31 import Pipes ((>->))
32 import Prelude (logBase, ceiling, Num(..), (/), (^), fromIntegral, Double)
33 import Symantic.CLI as CLI
34 import Text.Show (Show(..))
35 import System.IO (IO, FilePath)
36 import qualified Crypto.Hash as Crypto
37 import qualified Data.Aeson as JSON
38 import qualified Data.ByteArray as ByteArray
39 import qualified Data.ByteString as BS
40 import qualified Data.ByteString.Char8 as BS8
41 import qualified Data.ByteString.Lazy as BSL
42 import qualified Data.List as List
43 import qualified Data.Text as T
44 import qualified Data.Text.Encoding as T
45 import qualified Data.Text.Lazy as TL
46 import qualified Data.Text.Lazy.Builder as TLB
47 import qualified Data.Text.Lazy.Builder.Int as TLB
48 import qualified Data.Text.Lazy.Encoding as TL
49 import qualified Data.Text.Lazy.IO as TL
50 import qualified Data.Time as Time
51 import qualified Lens.Family as Lens
52 import qualified Lens.Family.State.Strict as Lens
53 import qualified Pipes as Pip
54 import qualified Pipes.ByteString as PipBS
55 import qualified Pipes.Group as Pip
56 import qualified Pipes.Prelude as Pip
57 import qualified Pipes.Aeson as PipJSON (DecodingError(..))
58 import qualified Pipes.Aeson.Unchecked as PipJSON
59 import qualified Pipes.Safe as Pip
60 import qualified Pipes.Safe.Prelude as Pip
61 import qualified Pipes.Text as PipText
62 import qualified Pipes.Text.Encoding as PipText
63 import qualified Pipes.Text.IO as PipText
64 import qualified Symantic.Document as Doc
65 import qualified System.FilePath as FP
66 import qualified System.IO as IO
67 import qualified System.Posix as Posix
68 import qualified System.Random as Rand
69 import qualified Voting.Protocol as VP
70
71 import Hjugement.CLI.Utils
72
73 -- * trustee
74 data Trustee_Params = Trustee_Params
75 { trustee_crypto :: VP.FFC
76 } deriving (Show)
77
78 api_trustee =
79 "Commands for a trustee."
80 `helps`
81 command "trustee" $
82 rule "TrusteeParams"
83 (Trustee_Params
84 <$> api_param_crypto
85 ) <?> (
86 api_trustee_generate <!>
87 api_trustee_decrypt
88 )
89 <!> api_help False
90
91 run_trustee globParams =
92 (\params ->
93 run_trustee_generate globParams params :!:
94 run_trustee_decrypt globParams params
95 ) :!:
96 run_help api_trustee
97
98 -- ** generate
99 api_trustee_generate =
100 "Run by a trustee to generate a share of an election key.\
101 \ Such a share consists of a private key and a public key with a certificate.\
102 \ Generated files are stored in the current directory with\
103 \ a name that starts with "<>fileRef "ID"<>",\
104 \ where "<>fileRef "ID"<>" is a short fingerprint of the public key.\
105 \ The private key is stored in "<>fileRef "ID.privkey"<>" and must be\
106 \ secured by the trustee. The public key is stored in "<>fileRef "ID.pubkey"<>" and must\
107 \ be sent to the election administrator."
108 `helps`
109 command "generate" $
110 response @()
111 run_trustee_generate
112 Global_Params{..}
113 o@Trustee_Params{..} =
114 VP.reify trustee_crypto $ \(crypto::Proxy c) -> do
115 keys@(secKey, pubKey) <- Pip.liftIO $ Rand.getStdRandom $ runState $ do
116 secKey <- VP.randomSecretKey @c
117 pubKey <- VP.proveIndispensableTrusteePublicKey secKey
118 return (secKey, pubKey)
119 let pubIdent =
120 T.unpack $ T.toUpper $ T.take 8 $
121 VP.hexHash $ VP.bytesNat $
122 VP.trustee_PublicKey pubKey
123 runPipe $ do
124 Pip.each [pubIdent] >-> pipeInfo (\ident ->
125 "Generated trustee keypair "<>ident<>
126 " in "<>(global_dir FP.</> ident)<>".{privkey,pubkey}"
127 ) >-> Pip.drain
128 Pip.each [secKey] >-> writeJSON 0o400 (global_dir FP.</> pubIdent FP.<.>"privkey")
129 Pip.each [pubKey] >-> writeJSON 0o444 (global_dir FP.</> pubIdent FP.<.>"pubkey")
130 return ()
131
132 -- ** decrypt
133 data TrusteeDecrypt_Params = TrusteeDecrypt_Params
134 { trusteeDecrypt_privkey :: FilePath
135 , trusteeDecrypt_url :: FilePath
136 } deriving (Show)
137
138 api_trustee_decrypt =
139 "This command is run by each trustee to perform a partial decryption."
140 `helps`
141 command "decrypt" $
142 rule "TrusteeDecryptParams"
143 (TrusteeDecrypt_Params
144 <$> api_param_privkey
145 <*> api_param_url)
146 <?> response @(Maybe (VP.DecryptionShare ()))
147 where
148 api_param_privkey =
149 "Read private key from file "<>ref"FILE"<>"."
150 `helps`
151 requiredTag "privkey" (var "FILE")
152
153 run_trustee_decrypt
154 Global_Params{..}
155 o@Trustee_Params{..}
156 TrusteeDecrypt_Params{..} =
157 VP.reify trustee_crypto $ \(crypto::Proxy c) -> runMaybeT $ do
158 (secKey::VP.E c) <- loadJSON trusteeDecrypt_privkey
159 let pubKey = VP.publicKey secKey
160 let trusteeKeysPath = trusteeDecrypt_url FP.</> "public_keys.jsons"
161 -- Check that the public key is amongst the public keys of the election
162 keys <- runPipeWithError $
163 Pip.toListM' $
164 readJSON trusteeKeysPath
165 >-> Pip.filter ((pubKey ==) . VP.trustee_PublicKey)
166 case () of
167 () | null keys -> outputError $
168 "the public key associated with the given secret key "<>
169 "is not within the list of public trustee keys of the election.\n"<>
170 Doc.ul
171 [ "List of trustees' public keys: "<>Doc.from trusteeKeysPath
172 , "Trustee's public key: "<>Doc.from (show (VP.nat pubKey))
173 ]<>"\n"
174 () | List.length keys > 1 -> outputError $
175 "the public key associated with the given secret key "<>
176 "appears more than one time in the list of public trustee keys of the election.\n"<>
177 Doc.ul
178 [ "List of trustees' public keys: "<>Doc.from trusteeKeysPath
179 , "Trustee's public key: "<>Doc.from (show (VP.nat pubKey))
180 ]<>"\n"
181 () -> do
182 -- Tally the encrypted ballots
183 -- FIXME: actually support fetching through an URL
184 let ballotsPath = trusteeDecrypt_url FP.</> "ballots.jsons"
185 (encTally, numBallots) <- runPipeWithError $
186 Pip.fold'
187 (flip VP.insertEncryptedTally)
188 VP.emptyEncryptedTally id $
189 readJSON ballotsPath
190 decShare <- Pip.liftIO $
191 Rand.getStdRandom $ runState $
192 VP.proveDecryptionShare encTally secKey
193 return (coerce decShare :: VP.DecryptionShare ())