Skip to content

Commit

Permalink
Add sender party to authenticated messages
Browse files Browse the repository at this point in the history
Used to check the sender is the signer.
  • Loading branch information
ffakenz authored and v0d1ch committed Jul 5, 2023
1 parent 298fbf9 commit 0e5ee7d
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 15 deletions.
13 changes: 7 additions & 6 deletions hydra-node/src/Hydra/Network/Authenticate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ 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))
import Hydra.Party (Party (Party, vkey), deriveParty)
import Hydra.Prelude

-- | Represents a signed message over the network.
Expand All @@ -14,6 +14,7 @@ import Hydra.Prelude
data Authenticated msg = Authenticated
{ payload :: msg
, signature :: Signature msg
, party :: Party
}
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON)
Expand All @@ -23,10 +24,10 @@ instance (Arbitrary msg, SignableRepresentation msg) => Arbitrary (Authenticated
shrink = genericShrink

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

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

-- | Middleware used to sign messages before broadcasting them to other peers
-- and verify signed messages upon receiving.
Expand All @@ -47,8 +48,8 @@ withAuthentication ::
withAuthentication signingKey parties withRawNetwork callback action = do
withRawNetwork checkSignature authenticate
where
checkSignature (Authenticated msg sig) = do
when (any (\Party{vkey} -> verify vkey sig msg) parties) $
checkSignature (Authenticated msg sig party@Party{vkey = partyVkey}) = do
when (verify partyVkey sig msg && elem party parties) $
callback msg
authenticate = \Network{broadcast} ->
action $ Network{broadcast = \msg -> broadcast (Authenticated msg (sign signingKey msg))}
action $ Network{broadcast = \msg -> broadcast (Authenticated msg (sign signingKey msg) (deriveParty signingKey))}
17 changes: 8 additions & 9 deletions hydra-node/test/Hydra/Network/AuthenticateSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ import Hydra.Network (Network (..))
import Hydra.Network.Authenticate (Authenticated (Authenticated), withAuthentication)
import Hydra.Network.HeartbeatSpec (noop)
import Hydra.NetworkSpec (prop_canRoundtripCBOREncoding)
import Test.Hydra.Fixture (aliceSk, bob, bobSk)
import Hydra.Party (deriveParty)
import Test.Hydra.Fixture (alice, aliceSk, bob, bobSk, carol, carolSk)
import Test.QuickCheck (generate, listOf)

spec :: Spec
Expand All @@ -33,7 +34,7 @@ spec = parallel $ do
aliceSk
[bob]
( \incoming _ -> do
incoming (Authenticated "1" (sign bobSk "1"))
incoming (Authenticated "1" (sign bobSk "1") bob)
)
(captureIncoming receivedMessages)
$ \_ ->
Expand All @@ -51,8 +52,8 @@ spec = parallel $ do
aliceSk
[bob]
( \incoming _ -> do
incoming (Authenticated "1" (sign bobSk "1"))
incoming (Authenticated "2" (sign aliceSk "2"))
incoming (Authenticated "1" (sign bobSk "1") bob)
incoming (Authenticated "2" (sign aliceSk "2") alice)
)
(captureIncoming receivedMessages)
$ \_ ->
Expand All @@ -62,7 +63,7 @@ spec = parallel $ do

receivedMsgs `shouldBe` ["1"]

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

Expand All @@ -78,7 +79,7 @@ spec = parallel $ do

readTVarIO receivedMessages

receivedMsgs `shouldBe` ["1"]
receivedMsgs `shouldBe` []

it "authenticate the message to broadcast" $ do
signingKey <- generate arbitrary
Expand All @@ -93,16 +94,14 @@ spec = parallel $ do

readTVarIO sentMessages

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

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


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

instance Arbitrary Msg where
arbitrary = Msg . pack <$> listOf arbitrary

0 comments on commit 0e5ee7d

Please sign in to comment.