summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
blob: ec21254972fc488e055a69562d78b37474a0cd75 (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
{-# LANGUAGE DeriveGeneric, FlexibleInstances #-}

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

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

import Val
import Memory

import GHC.Generics (Generic)
import Data.Aeson
import qualified Data.Aeson.Types as Aeson

-- | 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)

-- | High level protocol.
data Proto a
	= Proto a
	-- ^ either Entered or Seen
	| Rejected (Activity Entered)
	-- ^ sent by user to indicate when an Entered value was rejected.
	deriving (Show, Generic)

instance DataSize a => DataSize (Proto a) where
	dataSize (Proto a) = dataSize a
	dataSize (Rejected a) = dataSize a

-- | A Proto activity (either Entered or Seen) with a pointer
-- to the Activity before this one.
--
-- The Signature is over both the data in the activity, and its pointer.
data Activity a = Activity
	{ activity :: Proto a
	, prevActivity :: (Maybe Hash)
	, signature :: Signature
	}
	deriving (Show, Generic)

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

newtype Signature = Signature Val
	deriving (Show, Generic)

instance DataSize Signature where
	dataSize _ = 42 -- FIXME real size here

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)

instance ToJSON Seen
instance FromJSON Seen
instance ToJSON Entered
instance FromJSON Entered
instance ToJSON (Activity Seen)
instance FromJSON (Activity Seen)
instance ToJSON (Activity Entered)
instance FromJSON (Activity Entered)
instance ToJSON Signature
instance FromJSON Signature
instance ToJSON Hash
instance FromJSON Hash
instance ToJSON HashMethod
instance FromJSON HashMethod

-- | Nicer JSON encoding for sum types.
sumOptions :: Aeson.Options
sumOptions = defaultOptions { Aeson.sumEncoding = Aeson.ObjectWithSingleField }

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

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