Skip to content

Commit

Permalink
Refactor: introduce AuthenticatedMessage and SignedMessage
Browse files Browse the repository at this point in the history
An AtuhenticatedMessager is a SignedMessage which we authenticated.
  • Loading branch information
pgrange authored and v0d1ch committed Jul 5, 2023
1 parent 0e5ee7d commit 05b5088
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 31 deletions.
34 changes: 22 additions & 12 deletions hydra-node/src/Hydra/Network/Authenticate.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,42 @@
{-# LANGUAGE DuplicateRecordFields #-}

module Hydra.Network.Authenticate where

import Cardano.Crypto.Util (SignableRepresentation)
import Hydra.Crypto (HydraKey, Key (SigningKey), Signature, sign, verify)
import Hydra.Network (Network (Network, broadcast), NetworkComponent)
import Hydra.Party (Party (Party, vkey), deriveParty)
import Hydra.Party (Party (Party, vkey))
import Hydra.Prelude

-- | Represents a signed message over the network.
-- Becomes valid once its receivers verify it against its other peers
-- verification keys.
-- Messages are signed and turned into authenticated messages before
-- broadcasting them to other peers.
data Authenticated msg = Authenticated
data Signed msg = Signed
{ payload :: msg
, signature :: Signature msg
, party :: Party
}
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON)

instance (Arbitrary msg, SignableRepresentation msg) => Arbitrary (Authenticated msg) where
data Authenticated msg = Authenticated
{ payload :: msg
, party :: Party
}
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON)

instance (Arbitrary msg, SignableRepresentation msg) => Arbitrary (Signed msg) where
arbitrary = genericArbitrary
shrink = genericShrink

instance ToCBOR msg => ToCBOR (Authenticated msg) where
toCBOR (Authenticated msg sig party) = toCBOR msg <> toCBOR sig <> toCBOR party
instance ToCBOR msg => ToCBOR (Signed msg) where
toCBOR (Signed msg sig party) = toCBOR msg <> toCBOR sig <> toCBOR party

instance FromCBOR msg => FromCBOR (Authenticated msg) where
fromCBOR = Authenticated <$> fromCBOR <*> fromCBOR <*> fromCBOR
instance FromCBOR msg => FromCBOR (Signed msg) where
fromCBOR = Signed <$> fromCBOR <*> fromCBOR <*> fromCBOR

-- | Middleware used to sign messages before broadcasting them to other peers
-- and verify signed messages upon receiving.
Expand All @@ -42,14 +51,15 @@ withAuthentication ::
-- Other party members
[Party] ->
-- The underlying raw network.
NetworkComponent m (Authenticated msg) a ->
NetworkComponent m (Signed msg) a ->
-- The node internal authenticated network.
NetworkComponent m msg a
NetworkComponent m (Authenticated msg) a
withAuthentication signingKey parties withRawNetwork callback action = do
withRawNetwork checkSignature authenticate
where
checkSignature (Authenticated msg sig party@Party{vkey = partyVkey}) = do
checkSignature (Signed msg sig party@Party{vkey = partyVkey}) = do
when (verify partyVkey sig msg && elem party parties) $
callback msg
callback $
Authenticated msg party
authenticate = \Network{broadcast} ->
action $ Network{broadcast = \msg -> broadcast (Authenticated msg (sign signingKey msg) (deriveParty signingKey))}
action $ Network{broadcast = \(Authenticated msg party) -> broadcast (Signed msg (sign signingKey msg) party)}
36 changes: 17 additions & 19 deletions hydra-node/test/Hydra/Network/AuthenticateSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,11 @@ import Control.Monad.IOSim (runSimOrThrow)
import Data.ByteString (pack)
import Hydra.Crypto (sign)
import Hydra.Network (Network (..))
import Hydra.Network.Authenticate (Authenticated (Authenticated), withAuthentication)
import Hydra.Network.Authenticate (Authenticated (..), Signed (Signed), withAuthentication)
import Hydra.Network.HeartbeatSpec (noop)
import Hydra.NetworkSpec (prop_canRoundtripCBOREncoding)
import Hydra.Party (deriveParty)
import Test.Hydra.Fixture (alice, aliceSk, bob, bobSk, carol, carolSk)
import Test.QuickCheck (generate, listOf)
import Test.QuickCheck (listOf)

spec :: Spec
spec = parallel $ do
Expand All @@ -28,50 +27,50 @@ spec = parallel $ do

it "pass the authenticated messages around" $ do
let receivedMsgs = runSimOrThrow $ do
receivedMessages <- newTVarIO ([] :: [ByteString])
receivedMessages <- newTVarIO ([] :: [Authenticated ByteString])

withAuthentication
aliceSk
[bob]
( \incoming _ -> do
incoming (Authenticated "1" (sign bobSk "1") bob)
incoming (Signed "1" (sign bobSk "1") bob)
)
(captureIncoming receivedMessages)
$ \_ ->
threadDelay 1

readTVarIO receivedMessages

receivedMsgs `shouldBe` ["1"]
receivedMsgs `shouldBe` [Authenticated "1" bob]

it "drop message coming from unknown party" $ do
let receivedMsgs = runSimOrThrow $ do
receivedMessages <- newTVarIO ([] :: [ByteString])
receivedMessages <- newTVarIO ([] :: [Authenticated ByteString])

withAuthentication
aliceSk
[bob]
( \incoming _ -> do
incoming (Authenticated "1" (sign bobSk "1") bob)
incoming (Authenticated "2" (sign aliceSk "2") alice)
incoming (Signed "1" (sign bobSk "1") bob)
incoming (Signed "2" (sign aliceSk "2") alice)
)
(captureIncoming receivedMessages)
$ \_ ->
threadDelay 1

readTVarIO receivedMessages

receivedMsgs `shouldBe` ["1"]
receivedMsgs `shouldBe` [Authenticated "1" bob]

it "drop message comming from party with wrong signature" $ do
let receivedMsgs = runSimOrThrow $ do
receivedMessages <- newTVarIO ([] :: [ByteString])
receivedMessages <- newTVarIO ([] :: [Authenticated ByteString])

withAuthentication
aliceSk
[bob, carol]
( \incoming _ -> do
incoming (Authenticated "1" (sign carolSk "1") bob)
incoming (Signed "1" (sign carolSk "1") bob)
)
(captureIncoming receivedMessages)
$ \_ ->
Expand All @@ -82,23 +81,22 @@ spec = parallel $ do
receivedMsgs `shouldBe` []

it "authenticate the message to broadcast" $ do
signingKey <- generate arbitrary
let someMessage = "1"
let someMessage = Authenticated "1" bob
sentMsgs = runSimOrThrow $ do
sentMessages <- newTVarIO ([] :: [Authenticated ByteString])
sentMessages <- newTVarIO ([] :: [Signed ByteString])

withAuthentication signingKey [] (captureOutgoing sentMessages) noop $ \Network{broadcast} -> do
withAuthentication bobSk [] (captureOutgoing sentMessages) noop $ \Network{broadcast} -> do
threadDelay 0.6
broadcast someMessage
threadDelay 1

readTVarIO sentMessages

sentMsgs `shouldBe` [Authenticated "1" (sign signingKey "1") (deriveParty signingKey)]
sentMsgs `shouldBe` [Signed "1" (sign bobSk "1") bob]

describe "Serialization" $ do
prop "can roundtrip CBOR encoding/decoding of Authenticated Hydra Message" $
prop_canRoundtripCBOREncoding @(Authenticated Msg)
prop "can roundtrip CBOR encoding/decoding of Signed Hydra Message" $
prop_canRoundtripCBOREncoding @(Signed Msg)

newtype Msg = Msg ByteString
deriving newtype (Eq, Show, ToCBOR, FromCBOR, SignableRepresentation)
Expand Down

0 comments on commit 05b5088

Please sign in to comment.