Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
pgrange committed Jul 4, 2023
1 parent f134261 commit 857cb8b
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 2 deletions.
4 changes: 4 additions & 0 deletions hydra-node/src/Hydra/Network/Authenticate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,10 @@ data Authenticated msg = Authenticated
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON)

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

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

Expand Down
16 changes: 14 additions & 2 deletions hydra-node/test/Hydra/Network/AuthenticateSpec.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,20 @@
{-# LANGUAGE TypeApplications #-}

module Hydra.Network.AuthenticateSpec where

import Hydra.Prelude
import Test.Hydra.Prelude

import Control.Concurrent.Class.MonadSTM (MonadSTM (readTVarIO), modifyTVar', newTVarIO)
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.HeartbeatSpec (noop)
import Hydra.NetworkSpec (prop_canRoundtripCBOREncoding)
import Test.Hydra.Fixture (aliceSk, bob, bobSk)
import Test.QuickCheck (generate)
import Hydra.Network.Authenticate (Authenticated (Authenticated), withAuthentication)
import Test.QuickCheck (generate, listOf, vectorOf)

spec :: Spec
spec = parallel $ do
Expand Down Expand Up @@ -72,3 +76,11 @@ spec = parallel $ do

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

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)

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

0 comments on commit 857cb8b

Please sign in to comment.