-
Notifications
You must be signed in to change notification settings - Fork 4
/
Copy pathMain.hs
118 lines (103 loc) · 3.58 KB
/
Main.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
-- | Entrypoint for testing interoperability.
--
-- Interoperability harness lives at <https://github.com/leastauthority/spake2-interop-test>
--
-- Any entry point for the harness needs to:
-- - take everything it needs as command-line parameters
-- - print the outbound message to stdout, base16-encoded
-- - read the inbound message from stdin, base16-encoded
-- - print the session key, base16-encoded
-- - terminate
--
-- Much of the code in here will probably move to the library as we figure out
-- what we need to do to implement the protocol properly.
module Main (main) where
import Protolude hiding (group, toS)
import Protolude.Conv (toS)
import Crypto.Hash (SHA256(..))
import Data.ByteArray.Encoding (convertFromBase, convertToBase, Base(Base16))
import Data.String (String)
import Options.Applicative
import System.IO (hFlush, hGetLine)
import qualified Crypto.Spake2 as Spake2
import Crypto.Spake2
( Password
, Protocol
, SideID(..)
, makeSymmetricProtocol
, makeAsymmetricProtocol
, makePassword
, spake2Exchange
)
import Crypto.Spake2.Group (AbelianGroup, Group(..))
import Crypto.Spake2.Groups (Ed25519(..))
data Config = Config Side Password deriving (Eq, Ord)
data Side = SideA | SideB | Symmetric deriving (Eq, Ord, Show)
configParser :: Parser Config
configParser =
Config
<$> argument sideParser (metavar "SIDE")
<*> argument passwordParser (metavar "PASSWORD")
where
sideParser = eitherReader $ \s ->
case s of
"A" -> pure SideA
"B" -> pure SideB
"Symmetric" -> pure Symmetric
unknown -> throwError $ "Unrecognized side: " <> unknown
passwordParser = makePassword . toS @String <$> str
-- | Terminate the test with a failure, printing a message to stderr.
abort :: HasCallStack => Text -> IO ()
abort message = do
hPutStrLn stderr ("ERROR: " <> message)
exitWith (ExitFailure 1)
runInteropTest
:: (HasCallStack, AbelianGroup group)
=> Protocol group SHA256
-> Password
-> Handle
-> Handle
-> IO ()
runInteropTest protocol password inH outH = do
sessionKey' <- spake2Exchange protocol password output input
case sessionKey' of
Left err -> abort $ show err
Right sessionKey -> output sessionKey
where
output :: ByteString -> IO ()
output message = do
hPutStrLn outH (convertToBase Base16 message :: ByteString)
hFlush outH
input :: IO (Either Text ByteString)
input = do
line <- hGetLine inH
case convertFromBase Base16 (toS line :: ByteString) of
Left err -> pure . Left . toS $ "Could not decode line (reason: " <> err <> "): " <> show line
Right bytes -> pure (Right bytes)
makeProtocolFromSide :: Side -> Protocol Ed25519 SHA256
makeProtocolFromSide side =
case side of
SideA -> makeAsymmetricProtocol hashAlg group m n idA idB Spake2.SideA
SideB -> makeAsymmetricProtocol hashAlg group m n idA idB Spake2.SideB
Symmetric -> makeSymmetricProtocol hashAlg group s idSymmetric
where
hashAlg = SHA256
group = Ed25519
m = arbitraryElement group ("M" :: ByteString)
n = arbitraryElement group ("N" :: ByteString)
s = arbitraryElement group ("symmetric" :: ByteString)
idA = SideID ""
idB = SideID ""
idSymmetric = SideID ""
main :: IO ()
main = do
Config side password <- execParser opts
let protocol = makeProtocolFromSide side
runInteropTest protocol password stdin stdout
exitSuccess
where
opts = info (helper <*> configParser)
(fullDesc <>
header "interop-entrypoint - tool to help test SPAKE2 interop")