summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2017-04-18 16:35:38 -0400
committerJoey Hess <joeyh@joeyh.name>2017-04-18 16:35:38 -0400
commitd73352f848b79224a94e531bb651897321064998 (patch)
tree4e4bb7f13113bfffc950a0451dd89b6ca8160070
parenta70548f6dade6d93d482510a1b68b99327ec7f4a (diff)
downloaddebug-me-d73352f848b79224a94e531bb651897321064998.tar.gz
initial Crypto
Will use Ed25519 because it's from DJB and well regarded and in common use now.
-rw-r--r--Crypto.hs24
-rw-r--r--Hash.hs3
-rw-r--r--Json.hs13
-rw-r--r--Log.hs3
-rw-r--r--Types.hs34
-rw-r--r--debug-me.cabal3
-rw-r--r--debug-me.hs4
-rw-r--r--protocol.txt41
8 files changed, 92 insertions, 33 deletions
diff --git a/Crypto.hs b/Crypto.hs
new file mode 100644
index 0000000..3d0529d
--- /dev/null
+++ b/Crypto.hs
@@ -0,0 +1,24 @@
+module Crypto where
+
+import Val
+import Hash
+import Types
+
+import qualified Crypto.PubKey.Ed25519 as Ed25519
+import Data.ByteArray (convert)
+import Crypto.Error
+
+dummySignature :: Signature
+dummySignature = Unsigned
+
+-- | Sign any Hashable value.
+sign :: Hashable v => Ed25519.SecretKey -> Ed25519.PublicKey -> v -> Signature
+sign sk pk v = Ed25519 $ Val $ convert $
+ Ed25519.sign sk pk $ val $ hashValue $ hash v
+
+-- | Verifiy a signature of any Hashable value.
+verify :: Hashable v => Ed25519.PublicKey -> v -> Signature -> Bool
+verify pk v (Ed25519 (Val s)) = case Ed25519.signature s of
+ CryptoPassed sig -> Ed25519.verify pk (val $ hashValue $ hash v) sig
+ CryptoFailed _ -> False
+verify _ _ Unsigned = False
diff --git a/Hash.hs b/Hash.hs
index ed4513b..2577c6b 100644
--- a/Hash.hs
+++ b/Hash.hs
@@ -50,7 +50,8 @@ instance Hashable Seen where
hash v = hash $ Tagged "Seen" [hash (seenData v)]
instance Hashable Signature where
- hash (Signature s) = hash $ Tagged "Signature" s
+ hash (Ed25519 s) = hash $ Tagged "Ed25519" s
+ hash Unsigned = hash $ Tagged "Unsigned" (mempty :: B.ByteString)
-- | Hash a list of hashes by hashing the concacenation of the hashes.
instance Hashable [Hash] where
diff --git a/Json.hs b/Json.hs
new file mode 100644
index 0000000..4486d21
--- /dev/null
+++ b/Json.hs
@@ -0,0 +1,13 @@
+module Json (
+ module Data.Aeson,
+ Generic,
+ sumOptions
+) where
+
+import GHC.Generics (Generic)
+import Data.Aeson
+import qualified Data.Aeson.Types as Aeson
+
+-- | Nicer JSON encoding for sum types.
+sumOptions :: Aeson.Options
+sumOptions = defaultOptions { Aeson.sumEncoding = Aeson.ObjectWithSingleField }
diff --git a/Log.hs b/Log.hs
index 8690f27..f483e7d 100644
--- a/Log.hs
+++ b/Log.hs
@@ -5,9 +5,8 @@ module Log where
import Types
import Hash
import Memory
+import Json
-import GHC.Generics (Generic)
-import Data.Aeson
import Data.Char
import Data.Either
import Data.Time.Clock.POSIX
diff --git a/Types.hs b/Types.hs
index ec21254..dbbb432 100644
--- a/Types.hs
+++ b/Types.hs
@@ -13,10 +13,7 @@ module Types (
import Val
import Memory
-
-import GHC.Generics (Generic)
-import Data.Aeson
-import qualified Data.Aeson.Types as Aeson
+import Json
-- | Things that the developer sees.
data Seen = Seen
@@ -67,12 +64,6 @@ instance DataSize a => DataSize (Activity a) where
+ 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
@@ -88,6 +79,16 @@ instance DataSize Hash where
data HashMethod = SHA256 | SHA3
deriving (Show, Generic, Eq)
+data Signature
+ = Ed25519 Val
+ | Unsigned
+ -- ^ Not used, but included to future-proof the JSON format.
+ deriving (Show, Generic)
+
+instance DataSize Signature where
+ dataSize (Ed25519 _) = 64
+ dataSize Unsigned = 0
+
instance ToJSON Seen
instance FromJSON Seen
instance ToJSON Entered
@@ -96,17 +97,11 @@ 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
@@ -118,3 +113,10 @@ instance ToJSON (Proto Entered) where
toEncoding = genericToEncoding sumOptions
instance FromJSON (Proto Entered) where
parseJSON = genericParseJSON sumOptions
+
+instance ToJSON Signature where
+ toJSON = genericToJSON sumOptions
+ toEncoding = genericToEncoding sumOptions
+instance FromJSON Signature where
+ parseJSON = genericParseJSON sumOptions
+
diff --git a/debug-me.cabal b/debug-me.cabal
index 62cfa4c..05ab1e9 100644
--- a/debug-me.cabal
+++ b/debug-me.cabal
@@ -38,10 +38,13 @@ Executable debug-me
, graphviz (== 2999.18.*)
, time (>= 1.6)
, unbounded-delays (>= 0.1)
+ , memory (>= 0.13)
Other-Modules:
CmdLine
+ Crypto
Graphviz
Hash
+ Json
Log
Memory
Pty
diff --git a/debug-me.hs b/debug-me.hs
index 8ff38ed..7a51613 100644
--- a/debug-me.hs
+++ b/debug-me.hs
@@ -11,6 +11,7 @@ import Log
import Graphviz
import Replay
import Session
+import Crypto
import Control.Concurrent
import Control.Concurrent.Async
@@ -332,9 +333,6 @@ isLegalEntered (Activity (Proto entered) hp sig) (Backlog (lastseen :| bl))
-- Developer should never send Rejected.
isLegalEntered (Activity (Rejected _) _ _) _ = False
-dummySignature :: Signature
-dummySignature = Signature mempty
-
-- | Temporary hack while user and developer share a process.
protocolError :: String -> IO a
protocolError e = do
diff --git a/protocol.txt b/protocol.txt
index 06c9454..10829c5 100644
--- a/protocol.txt
+++ b/protocol.txt
@@ -3,14 +3,12 @@ the two participants, known as the user and the developer.
The exact composition of the JSON objects is not described here; see
Types.hs for the data types that JSON serialization instances are derived
-from.
+from. The Activity type is the main message type.
-A debug-me session starts with the user sending an Activity Seen
-containing an introductory message, eg "debug-me session started".
-This first Activity Seen has Nothing as its prevActivity. All
-subsequent Activity sent by either the user or developer must have a
-prevActivity that points to the Hash of the previous activity.
-So a chain of Activity is built up.
+The first message in a debug-me session is sent by the user, and it has
+Nothing as its prevActivity. All subsequent messages sent by either the
+user or the developer must have a prevActivity that points to the Hash
+of a previous message. So a chain of messages is built up.
The exact details about how these objects are hashed is not described here;
see Hash.hs for the implementation. Note that the JSON strings are *not*
@@ -26,9 +24,9 @@ about it.
Since the goal of debug-me is to produce a proof of the sequence of events
that occurred in a session, that is a problem. Perhaps the developer was
-entering "y" in response to "Shutdown reactor?" at the same time
+entering "y" in response to "Display detailed reactor logs?" at the same time
that a new "Vent core to atmosphere?" question was being displayed!
-So, the debug-me protocol is designed to prevent such conflicts of opinion.
+The debug-me protocol is designed to prevent such conflicts of opinion.
The user only processes a new Activity Entered when either:
@@ -42,8 +40,8 @@ The user only processes a new Activity Entered when either:
(This allows the developer to enter a command quickly without waiting
for each letter to echo back to them.)
-When an Activity Entered does not meet these rules, the user sends it
-back in a Rejected message to let the developer know the input was not
+When an Activity Entered does not meet these rules, the user sends
+it back in a Rejected message to let the developer know the input was not
allowed.
The developer also checks the prevActivity of messages it receives
@@ -55,3 +53,24 @@ The developer accepts a new Activity Seen when either:
2. The Activity Seen has as its prevActivity an Activity Entered
that the developer generated, after the last Activity Seen
that the developer accepted.
+
+At the start of the debug-me session, Ed25519 session key pairs are
+generated by both the user and the developer. The very first
+message in the protocol is the user sending their session pubic key.
+
+Before the developer can do anything, they must send a message with their
+session key, and it must be accepted by the user. The developer must have
+a gpg private key, which is used to sign their session key.
+(The user may have a gpg private key, which will sign their session key
+if available, but this is optional.) The user will reject session keys
+that are not signed by a gpg key or when the gpg key is not one they
+trust.
+
+Note that there could be multiple developers, in which case each will
+send their session key before being able to do anything except observe
+the debug-me session.
+
+Each message in the debug-me session is signed by the party that sends it,
+using their session key. The hash of a message includes its signature, so
+the activity chain proves who sent a message, and who sent the message its
+prevActivity points to, etc.