summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
blob: 699fa59994f3a185759f28a096e97906aebc817f (plain)
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
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
{-# LANGUAGE DeriveGeneric, FlexibleInstances #-}

{- | Main types for debug-me
 -
 - Note that changing types in ways that change the cereal serialization
 - changes debug-me's wire format. Changing types in ways that change the
 - aeson serialization changes debug-me's log format.
 -}

module Types (
	module Types,
	Val(..)
) where

import Val
import Memory
import Serialization

-- | Things that the developer sees.
data Seen = Seen
	{ seenData :: Val
	}
	deriving (Show, Generic)

instance DataSize Seen where
	dataSize = dataSize . seenData

-- | Things that the developer enters.
data Entered = Entered
	{ enteredData :: Val
	, echoData :: Val
	-- ^ Data that is expected to be Seen, but has not been received
	-- at the time this was entered.
	}
	deriving (Show, Generic)

instance DataSize Entered where
	dataSize e = dataSize (enteredData e) + dataSize (echoData e)

-- | A message in the protocol.
data Message a
	= ActivityMessage (Activity a)
	| ControlMessage Control
	deriving (Show, Generic)

instance DataSize a => DataSize (Message a) where
	dataSize (ActivityMessage a) = dataSize a
	dataSize (ControlMessage c) = dataSize c

-- | An activity (either Entered or Seen) with a pointer
-- to a previous Activity.
--
-- The Signature is over both the data in the activity, and its pointer.
--
-- Note that the Signature is included in the Hash of an Activity,
-- which is why it's part of the Activity.
data Activity a = Activity
	{ activity :: a
	, prevActivity :: Maybe Hash
	, activitySignature :: Signature
	}
	deriving (Show, Generic)

instance DataSize a => DataSize (Activity a) where
	dataSize a = dataSize (activity a) 
		+ maybe 0 dataSize (prevActivity a) 
		+ dataSize (activitySignature a)

-- | A control message, which can be sent asynchronously.
data Control = Control
	{ control :: ControlAction
	, controlSignature :: Signature
	}
	deriving (Show, Generic)

instance DataSize Control where
	dataSize c = dataSize (control c)
		+ dataSize (controlSignature c)

data ControlAction
	= Rejected (Activity Entered)
	-- ^ sent by user to indicate when an Entered value was rejected.
	| SessionKey PublicKey
	-- ^ sent by user at start, and later by developer,
	-- to indicate their session key
	| SessionKeyAccepted PublicKey
	-- ^ sent by the user to in response to SessionKey
	| SessionKeyRejected PublicKey
	-- ^ sent by the user to in response to SessionKey
	deriving (Show, Generic)

instance DataSize ControlAction where
	dataSize (Rejected a) = dataSize a
	dataSize (SessionKey k) = dataSize k
	dataSize (SessionKeyAccepted k) = dataSize k
	dataSize (SessionKeyRejected k) = dataSize k

data Hash = Hash
	{ hashMethod :: HashMethod
	, hashValue :: Val
	}
	deriving (Show, Generic, Eq)

instance DataSize Hash where
	dataSize (Hash { hashMethod = SHA256 }) = 64
	dataSize (Hash { hashMethod = SHA3 }) = 56

-- | We use SHA256. (SHA3 is included to future proof, and because it
-- improves the generated JSON.)
data HashMethod = SHA256 | SHA3
	deriving (Show, Generic, Eq)

data Signature 
	= Ed25519Signature Val
	| OtherSignature Val
	-- ^ Not used, but included to future-proof the JSON format.
	deriving (Show, Generic)

instance DataSize Signature where
	dataSize (Ed25519Signature v) = dataSize v
	dataSize (OtherSignature v) = dataSize v

-- | A public key used for a debug-me session.
-- It may be signed with a gpg key.
data PublicKey = PublicKey Val (Maybe GpgSig)
	deriving (Show, Generic, Eq)

instance DataSize PublicKey where
	-- ed25519 public keys are 32 bytes
	dataSize (PublicKey _ ms) = 32 + maybe 0 dataSize ms

-- | A signature made with a gpg key.
newtype GpgSig = GpgSig Val
	deriving (Show, Generic, Eq)

instance DataSize GpgSig where
	dataSize (GpgSig s) = dataSize s

instance Serialize Seen
instance ToJSON Seen
instance FromJSON Seen
instance Serialize Entered
instance ToJSON Entered
instance FromJSON Entered
instance Serialize (Activity Seen)
instance ToJSON (Activity Seen)
instance FromJSON (Activity Seen)
instance Serialize (Activity Entered)
instance ToJSON (Activity Entered)
instance FromJSON (Activity Entered)
instance Serialize Control
instance ToJSON Control
instance FromJSON Control
instance Serialize Hash
instance ToJSON Hash
instance FromJSON Hash
instance Serialize HashMethod
instance ToJSON HashMethod
instance FromJSON HashMethod
instance Serialize PublicKey
instance ToJSON PublicKey
instance FromJSON PublicKey
instance Serialize GpgSig
instance ToJSON GpgSig
instance FromJSON GpgSig

instance Serialize (Message Seen)
instance ToJSON (Message Seen) where
	toJSON = genericToJSON sumOptions
	toEncoding = genericToEncoding sumOptions
instance FromJSON (Message Seen) where
	parseJSON = genericParseJSON sumOptions

instance Serialize (Message Entered)
instance ToJSON (Message Entered) where
	toJSON = genericToJSON sumOptions
	toEncoding = genericToEncoding sumOptions
instance FromJSON (Message Entered) where
	parseJSON = genericParseJSON sumOptions

instance Serialize Signature
instance ToJSON Signature where
	toJSON = genericToJSON sumOptions
	toEncoding = genericToEncoding sumOptions
instance FromJSON Signature where
	parseJSON = genericParseJSON sumOptions

instance Serialize ControlAction
instance ToJSON ControlAction where
	toJSON = genericToJSON sumOptions
	toEncoding = genericToEncoding sumOptions
instance FromJSON ControlAction where
	parseJSON = genericParseJSON sumOptions