diff --git a/cabal.project b/cabal.project index 8c942b7a78f..6a69d31fc22 100644 --- a/cabal.project +++ b/cabal.project @@ -40,11 +40,13 @@ package plutus-merkle-tree -- Always show detailed output for tests test-show-details: direct +-- NOTE: master somewhere ahead of 1.35.x, but holding enough of our upstream +-- contributions to use for us source-repository-package type: git - location: https://github.com/abailly-iohk/cardano-node - tag: b96c6b075718b2c9e9d17761d16b7ca601937c10 - --sha256: 1i3bxc12lsdr9l88l1w75844gwf43y8k6ysz5kx15pybkz1r1i5m + location: https://github.com/input-output-hk/cardano-node.git + tag: aed8e71339cf6c92847fff83fbd92be61e468174 + --sha256: 1j8lkrg8xz6gjaq8grx7vc4cynlz5x6n3cd9q4y5w3kzsd89072a subdir: cardano-api @@ -78,8 +80,8 @@ source-repository-package source-repository-package type: git location: https://github.com/input-output-hk/cardano-base - tag: 0f3a867493059e650cda69e20a5cbf1ace289a57 - --sha256: 0p0az3sbkhb7njji8xxdrfb0yx2gc8fmrh872ffm8sfip1w29gg1 + tag: a3c13fb11bc41fedff7885ca70a3b33f61fef4b5 + --sha256: 0h492cz9mvzbsl5yzvp3iq40c0z0j5hmrifdrnnqzzk02g9j9c4b subdir: base-deriving-via binary @@ -103,8 +105,8 @@ source-repository-package source-repository-package type: git location: https://github.com/input-output-hk/cardano-ledger - tag: ce3057e0863304ccb3f79d78c77136219dc786c6 - --sha256: 19ijcy1sl1iqa7diy5nsydnjsn3281kp75i2i42qv0fpn58238s9 + tag: f49879a79098d9372d63baa13b94a941a56eda34 + --sha256: 0i9x66yqkrvx2w79dy6lzlya82yxc8567rgjj828vc2d46d6nvx6 subdir: eras/alonzo/impl eras/alonzo/test-suite @@ -135,8 +137,8 @@ source-repository-package source-repository-package type: git location: https://github.com/input-output-hk/cardano-prelude - tag: bb4ed71ba8e587f672d06edf9d2e376f4b055555 - --sha256: 00h10l5mmiza9819p9v5q5749nb9pzgi20vpzpy1d34zmh6gf1cj + tag: 6ea36cf2247ac0bc33e08c327abec34dfd05bd99 + --sha256: 0z2y3wzppc12bpn9bl48776ms3nszw8j58xfsdxf97nzjgrmd62g subdir: cardano-prelude cardano-prelude-test @@ -170,8 +172,8 @@ source-repository-package source-repository-package type: git location: https://github.com/input-output-hk/ouroboros-network - tag: a65c29b6a85e90d430c7f58d362b7eb097fd4949 - --sha256: 1fmab5hmi1y8lss97xh6hhikmyhsx9x31yhvg6zpr2kcq7kc6qkf + tag: c764553561bed8978d2c6753d1608dc65449617a + --sha256: 0hdh7xdrvxw943r6qr0xr4kwszindh5mnsn1lww6qdnxnmn7wcsc subdir: monoidal-synchronisation network-mux diff --git a/hydra-cardano-api/src/Hydra/Cardano/Api.hs b/hydra-cardano-api/src/Hydra/Cardano/Api.hs index 71116924b3a..26895c5eff5 100644 --- a/hydra-cardano-api/src/Hydra/Cardano/Api.hs +++ b/hydra-cardano-api/src/Hydra/Cardano/Api.hs @@ -37,6 +37,7 @@ import Cardano.Api as X hiding ( AddressInEra (..), AddressTypeInEra (..), BalancedTxBody (..), + Key (..), KeyWitness, PlutusScript, Script (..), @@ -71,11 +72,13 @@ import Cardano.Api.Byron as X ( ) import Cardano.Api.Shelley as X ( Address (..), + Key (..), PlutusScriptOrReferenceInput (PScript), PoolId, ProtocolParameters (..), ShelleyGenesis (..), ShelleyLedgerEra, + SigningKey (..), VerificationKey (..), fromPlutusData, toPlutusData, diff --git a/hydra-cluster/bench/Bench/EndToEnd.hs b/hydra-cluster/bench/Bench/EndToEnd.hs index 2ec874e7ff6..e37742cef12 100644 --- a/hydra-cluster/bench/Bench/EndToEnd.hs +++ b/hydra-cluster/bench/Bench/EndToEnd.hs @@ -32,7 +32,7 @@ import Data.Time (UTCTime (UTCTime), nominalDiffTimeToSeconds, utctDayTime) import Hydra.Cardano.Api (Tx, TxId, UTxO, getVerificationKey) import Hydra.Cluster.Faucet (Marked (Fuel), seedFromFaucet) import Hydra.Cluster.Fixture (defaultNetworkId) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (generateSigningKey) import Hydra.Generator (ClientDataset (..), Dataset (..)) import Hydra.Ledger (txId) import Hydra.Logging (withTracerOutputTo) @@ -78,7 +78,7 @@ bench timeoutSeconds workDir dataset@Dataset{clientDatasets} clusterSize = failAfter timeoutSeconds $ do putTextLn "Starting benchmark" let cardanoKeys = map (\ClientDataset{signingKey} -> (getVerificationKey signingKey, signingKey)) clientDatasets - let hydraKeys = Hydra.generateSigningKey . show <$> [1 .. toInteger (length cardanoKeys)] + let hydraKeys = generateSigningKey . show <$> [1 .. toInteger (length cardanoKeys)] let parties = Set.fromList (deriveParty <$> hydraKeys) withOSStats workDir $ withCardanoNodeDevnet (contramap FromCardanoNode tracer) workDir $ \node@RunningNode{nodeSocket} -> do diff --git a/hydra-cluster/config/protocol-parameters.json b/hydra-cluster/config/protocol-parameters.json index 2ebd7495be2..1c160118c4b 100644 --- a/hydra-cluster/config/protocol-parameters.json +++ b/hydra-cluster/config/protocol-parameters.json @@ -381,5 +381,6 @@ "treasuryCut": 0.1, "txFeeFixed": 0, "txFeePerByte": 0, - "utxoCostPerWord": 34488 + "utxoCostPerWord": 34488, + "utxoCostPerByte": 4310 } diff --git a/hydra-cluster/hydra-cluster.cabal b/hydra-cluster/hydra-cluster.cabal index 53bd9c51a2c..89e5485f07f 100644 --- a/hydra-cluster/hydra-cluster.cabal +++ b/hydra-cluster/hydra-cluster.cabal @@ -1,6 +1,6 @@ cabal-version: 3.0 name: hydra-cluster -version: 0.6.0 +version: 0.7.0 synopsis: Integration test suite using a local cluster of cardano and hydra nodes diff --git a/hydra-cluster/src/Hydra/Cluster/Fixture.hs b/hydra-cluster/src/Hydra/Cluster/Fixture.hs index ba6584093a4..52d47e7bc4a 100644 --- a/hydra-cluster/src/Hydra/Cluster/Fixture.hs +++ b/hydra-cluster/src/Hydra/Cluster/Fixture.hs @@ -8,8 +8,7 @@ import Hydra.Prelude import Hydra.Cardano.Api (NetworkId) import qualified Hydra.Cardano.Api as Api import Hydra.ContestationPeriod (ContestationPeriod (..)) -import Hydra.Crypto (deriveVerificationKey, generateSigningKey) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, SigningKey, VerificationKey, generateSigningKey, getVerificationKey) import Hydra.Party (Party, deriveParty) alice, bob, carol :: Party @@ -17,15 +16,15 @@ alice = deriveParty aliceSk bob = deriveParty bobSk carol = deriveParty carolSk -aliceSk, bobSk, carolSk :: Hydra.SigningKey +aliceSk, bobSk, carolSk :: SigningKey HydraKey aliceSk = generateSigningKey "alice" bobSk = generateSigningKey "bob" carolSk = generateSigningKey "carol" -aliceVk, bobVk, carolVk :: Hydra.VerificationKey -aliceVk = deriveVerificationKey aliceSk -bobVk = deriveVerificationKey bobSk -carolVk = deriveVerificationKey carolSk +aliceVk, bobVk, carolVk :: VerificationKey HydraKey +aliceVk = getVerificationKey aliceSk +bobVk = getVerificationKey bobSk +carolVk = getVerificationKey carolSk cperiod :: ContestationPeriod cperiod = UnsafeContestationPeriod 10 diff --git a/hydra-cluster/src/HydraNode.hs b/hydra-cluster/src/HydraNode.hs index 600f4e46830..53718c8aaf1 100644 --- a/hydra-cluster/src/HydraNode.hs +++ b/hydra-cluster/src/HydraNode.hs @@ -38,8 +38,7 @@ import qualified Data.ByteString as BS import qualified Data.List as List import qualified Data.Text as T import Hydra.Cluster.Util (readConfigFile) -import Hydra.Crypto (deriveVerificationKey, serialiseSigningKeyToRawBytes, serialiseVerificationKeyToRawBytes) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey) import Hydra.Ledger.Cardano () import Hydra.Logging (Tracer, traceWith) import Hydra.Network (Host (Host)) @@ -203,7 +202,7 @@ withHydraCluster :: Int -> -- | NOTE: This decides on the size of the cluster! [(VerificationKey PaymentKey, SigningKey PaymentKey)] -> - [Hydra.SigningKey] -> + [SigningKey HydraKey] -> (NonEmpty HydraClient -> IO ()) -> IO () withHydraCluster tracer workDir nodeSocket firstNodeId allKeys hydraKeys action = do @@ -225,7 +224,7 @@ withHydraCluster tracer workDir nodeSocket firstNodeId allKeys hydraKeys action [] -> action (fromList $ reverse clients) (nodeId : rest) -> do let hydraSKey = hydraKeys Prelude.!! (nodeId - firstNodeId) - hydraVKeys = map deriveVerificationKey $ filter (/= hydraSKey) hydraKeys + hydraVKeys = map getVerificationKey $ filter (/= hydraSKey) hydraKeys cardanoVerificationKeys = [workDir show i <.> "vk" | i <- allNodeIds, i /= nodeId] cardanoSigningKey = workDir show nodeId <.> "sk" chainConfig = @@ -252,8 +251,8 @@ withHydraNode :: ChainConfig -> FilePath -> Int -> - Hydra.SigningKey -> - [Hydra.VerificationKey] -> + SigningKey HydraKey -> + [VerificationKey HydraKey] -> [Int] -> (HydraClient -> IO a) -> IO a @@ -265,10 +264,10 @@ withHydraNode tracer chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNod let cardanoLedgerProtocolParametersFile = dir "protocol-parameters.json" readConfigFile "protocol-parameters.json" >>= writeFileBS cardanoLedgerProtocolParametersFile let hydraSigningKey = dir (show hydraNodeId <> ".sk") - BS.writeFile hydraSigningKey (serialiseSigningKeyToRawBytes hydraSKey) + BS.writeFile hydraSigningKey (serialiseToRawBytes hydraSKey) hydraVerificationKeys <- forM (zip [1 ..] hydraVKeys) $ \(i :: Int, vKey) -> do let filepath = dir (show i <> ".vk") - filepath <$ BS.writeFile filepath (serialiseVerificationKeyToRawBytes vKey) + filepath <$ BS.writeFile filepath (serialiseToRawBytes vKey) let ledgerConfig = CardanoLedgerConfig { cardanoLedgerGenesisFile diff --git a/hydra-cluster/test/Test/CardanoNodeSpec.hs b/hydra-cluster/test/Test/CardanoNodeSpec.hs index 50509cf2e01..777c39ed6b7 100644 --- a/hydra-cluster/test/Test/CardanoNodeSpec.hs +++ b/hydra-cluster/test/Test/CardanoNodeSpec.hs @@ -20,7 +20,7 @@ spec = do -- false positives test errors in case someone uses an "untested" / -- different than in shell.nix version of cardano-node and cardano-cli. it "has expected cardano-node version available" $ - getCardanoNodeVersion >>= (`shouldContain` "1.35.0") + getCardanoNodeVersion >>= (`shouldContain` "1.35.3") -- NOTE: We hard-code the expected networkId here to detect any change to the -- genesis-shelley.json diff --git a/hydra-node/golden/VerificationKey HydraKey.json b/hydra-node/golden/VerificationKey HydraKey.json new file mode 100644 index 00000000000..0baeffb7d16 --- /dev/null +++ b/hydra-node/golden/VerificationKey HydraKey.json @@ -0,0 +1,10 @@ +{ + "samples": [ + "8b8d8971de75cb147c66bf22a109c7d64d667e1e866c91182d8c987cdc462b1c", + "0a808c17865dbb543c704d11d6c9ee282f3f873b16857c478b629914d74a845b", + "e0fa61ce94fc5cd993c6329eb9a79171d5366024e1706a9c6de31ea804c3186a", + "1f244fd970279441beccbf8597df02e69ee0c4d1a7ca27b430603f334a5057ba", + "e06298a9d25522cf1c7a69655ffec31a872ab7d819b8a9639ff7c109efeef24e" + ], + "seed": 914957528 +} \ No newline at end of file diff --git a/hydra-node/src/Hydra/Chain/Direct/Context.hs b/hydra-node/src/Hydra/Chain/Direct/Context.hs index 03e125f44db..79d8d3c5277 100644 --- a/hydra-node/src/Hydra/Chain/Direct/Context.hs +++ b/hydra-node/src/Hydra/Chain/Direct/Context.hs @@ -9,6 +9,7 @@ import Hydra.Cardano.Api ( NetworkId (..), NetworkMagic (..), PaymentKey, + SigningKey, Tx, UTxO, VerificationKey, @@ -28,7 +29,7 @@ import Hydra.Chain.Direct.State ( observeTx, ) import Hydra.ContestationPeriod (ContestationPeriod) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, generateSigningKey) import Hydra.Ledger.Cardano (genOneUTxOFor, genTxIn, genUTxOAdaOnlyOfSize, genVerificationKey, renderTx) import Hydra.Ledger.Cardano.Evaluate (genPointInTime, genPointInTimeAfter) import Hydra.Party (Party, deriveParty) @@ -44,7 +45,7 @@ import Test.QuickCheck (choose, elements, frequency, vector) -- be coherent. data HydraContext = HydraContext { ctxVerificationKeys :: [VerificationKey PaymentKey] - , ctxHydraSigningKeys :: [Hydra.SigningKey] + , ctxHydraSigningKeys :: [SigningKey HydraKey] , ctxNetworkId :: NetworkId , ctxContestationPeriod :: ContestationPeriod } @@ -73,7 +74,7 @@ genHydraContext maxParties = choose (1, maxParties) >>= genHydraContextFor genHydraContextFor :: Int -> Gen HydraContext genHydraContextFor n = do ctxVerificationKeys <- replicateM n genVerificationKey - ctxHydraSigningKeys <- fmap Hydra.generateSigningKey <$> vector n + ctxHydraSigningKeys <- fmap generateSigningKey <$> vector n ctxNetworkId <- Testnet . NetworkMagic <$> arbitrary ctxContestationPeriod <- arbitrary pure $ diff --git a/hydra-node/src/Hydra/Crypto.hs b/hydra-node/src/Hydra/Crypto.hs index 470f4848a0d..94e871ad261 100644 --- a/hydra-node/src/Hydra/Crypto.hs +++ b/hydra-node/src/Hydra/Crypto.hs @@ -1,15 +1,24 @@ -- | Hydra multi-signature credentials and cryptographic primitives used to sign -- and verify snapshots (or any messages) within the Hydra protocol. -- --- Currently this interface is only supporting naiive, concatenated +-- We are re-using the 'Key' interface of 'cardano-api' for a consistent +-- representation. For example: Cardano credentials are 'VerificationKey +-- PaymentKey', Hydra credentials are 'VerificationKey HydraKey'. +-- +-- Currently 'MultiSignature' interface is only supporting naiive, concatenated -- multi-signatures and will change when we adopt aggregated multi-signatures -- including aggregate keys. --- --- It is recommended to import this module qualified to avoid confusion with --- Cardano keys & signatures. -module Hydra.Crypto where +module Hydra.Crypto ( + -- * Cardano Key interface + Key (..), -import Hydra.Prelude hiding (show) + -- * Hydra specifics + Hash (HydraKeyHash), + AsType (AsHydraKey), + module Hydra.Crypto, +) where + +import Hydra.Prelude hiding (Key, show) import Cardano.Crypto.DSIGN ( ContextDSIGN, @@ -17,6 +26,7 @@ import Cardano.Crypto.DSIGN ( SigDSIGN, SignKeyDSIGN, VerKeyDSIGN, + algorithmNameDSIGN, deriveVerKeyDSIGN, genKeyDSIGN, hashVerKeyDSIGN, @@ -30,78 +40,116 @@ import Cardano.Crypto.DSIGN ( signDSIGN, verifyDSIGN, ) -import Cardano.Crypto.Hash (Blake2b_256, Hash, castHash) -import Cardano.Crypto.Seed (mkSeedFromBytes) +import qualified Cardano.Crypto.DSIGN as Crypto +import Cardano.Crypto.Hash (Blake2b_256, castHash, hashFromBytes, hashToBytes) +import qualified Cardano.Crypto.Hash as Crypto +import Cardano.Crypto.Seed (getSeedBytes, mkSeedFromBytes) import Cardano.Crypto.Util (SignableRepresentation) import qualified Data.Aeson as Aeson import qualified Data.ByteString as BS import qualified Data.ByteString.Base16 as Base16 import qualified Data.Map as Map -import Hydra.Cardano.Api (HasTypeProxy (..), SerialiseAsRawBytes (..), serialiseToRawBytesHexText) +import Hydra.Cardano.Api ( + AsType (AsHash, AsSigningKey, AsVerificationKey), + HasTextEnvelope (..), + HasTypeProxy (..), + Hash, + Key (..), + SerialiseAsCBOR, + SerialiseAsRawBytes (..), + serialiseToRawBytesHexText, + ) import qualified Hydra.Contract.HeadState as OnChain import qualified Plutus.V2.Ledger.Api as Plutus import Test.QuickCheck.Instances.ByteString () import Text.Show (Show (..)) --- | The used signature algorithm -type SignAlg = Ed25519DSIGN - -- * Hydra keys --- | Hydra signing key which can be used to 'sign' messages and 'aggregate' --- multi-signatures or 'deriveVerificationKey'. --- --- REVIEW: Maybe rewrite Show instance to /not/ expose secret, eg. 8 bytes from --- the hash of the key? Although both, cardano-api and cardano-crypto-class are --- both deriving this and thus showing secret key material as well. -newtype SigningKey = HydraSigningKey (SignKeyDSIGN SignAlg) - deriving (Eq, Show) - -instance Arbitrary SigningKey where +-- | Hydra keys (keyrole) which can be used to 'sign' and 'verify' messages, as +-- well as 'aggregate' multi-signatures. +data HydraKey + +instance HasTypeProxy HydraKey where + data AsType HydraKey = AsHydraKey + proxyToAsType _ = AsHydraKey + +-- | Hashes of Hydra keys +newtype instance Hash HydraKey + = HydraKeyHash (Crypto.Hash Blake2b_256 (VerificationKey HydraKey)) + deriving stock (Ord, Eq, Show) + +instance SerialiseAsRawBytes (Hash HydraKey) where + serialiseToRawBytes (HydraKeyHash vkh) = hashToBytes vkh + + deserialiseFromRawBytes (AsHash AsHydraKey) bs = + HydraKeyHash <$> hashFromBytes bs + +instance Key HydraKey where + -- Hydra verification key, which can be used to 'verify' signed messages. + newtype VerificationKey HydraKey + = HydraVerificationKey (VerKeyDSIGN Ed25519DSIGN) + deriving (Eq, Show) + deriving newtype (ToCBOR, FromCBOR) + deriving anyclass (SerialiseAsCBOR) + + -- Hydra signing key which can be used to 'sign' messages and 'aggregate' + -- multi-signatures or 'deriveVerificationKey'. + -- + -- REVIEW: Maybe rewrite Show instance to /not/ expose secret, eg. 8 bytes + -- from the hash of the key? Although both, cardano-api and + -- cardano-crypto-class are both deriving this and thus showing secret key + -- material as well. + newtype SigningKey HydraKey + = HydraSigningKey (SignKeyDSIGN Ed25519DSIGN) + deriving (Eq, Show) + deriving newtype (ToCBOR, FromCBOR) + deriving anyclass (SerialiseAsCBOR) + + -- Get the 'VerificationKey' for a given 'SigningKey'. + getVerificationKey (HydraSigningKey sk) = + HydraVerificationKey $ deriveVerKeyDSIGN sk + + -- Create a new 'SigningKey' from a 'Seed'. See 'generateSigningKey' + deterministicSigningKey AsHydraKey = + generateSigningKey . getSeedBytes + + -- Get the number of bytes required to seed a signing key with + -- 'deterministicSigningKey'. + deterministicSigningKeySeedSize AsHydraKey = + seedSizeDSIGN (Proxy :: Proxy Ed25519DSIGN) + + -- Get the verification key hash of a 'VerificationKey'. See 'Blake2b_256' for + -- info on the used hashing algorithm. + verificationKeyHash (HydraVerificationKey vk) = + HydraKeyHash . castHash $ hashVerKeyDSIGN vk + +instance Arbitrary (SigningKey HydraKey) where arbitrary = generateSigningKey <$> arbitrary --- | Serialise the signing key material as raw bytes. -serialiseSigningKeyToRawBytes :: SigningKey -> ByteString -serialiseSigningKeyToRawBytes (HydraSigningKey sk) = rawSerialiseSignKeyDSIGN sk +instance SerialiseAsRawBytes (SigningKey HydraKey) where + serialiseToRawBytes (HydraSigningKey sk) = + rawSerialiseSignKeyDSIGN sk --- | Deserialise a signing key from raw bytes. -deserialiseSigningKeyFromRawBytes :: MonadFail m => ByteString -> m SigningKey -deserialiseSigningKeyFromRawBytes bytes = - case rawDeserialiseSignKeyDSIGN bytes of - Nothing -> fail "failed to deserialise signing key" - Just key -> pure $ HydraSigningKey key - --- | Get the 'VerificationKey' for a given 'SigningKey'. -deriveVerificationKey :: SigningKey -> VerificationKey -deriveVerificationKey (HydraSigningKey sk) = HydraVerificationKey (deriveVerKeyDSIGN sk) - --- | Create a new 'SigningKey' from a 'ByteString' seed. The created keys are --- not random and insecure, so don't use this in production code! -generateSigningKey :: ByteString -> SigningKey -generateSigningKey seed = - HydraSigningKey . genKeyDSIGN $ mkSeedFromBytes padded - where - needed = fromIntegral $ seedSizeDSIGN (Proxy :: Proxy SignAlg) - provided = BS.length seed - padded = seed <> BS.pack (replicate (needed - provided) 0) + deserialiseFromRawBytes (AsSigningKey AsHydraKey) bs = + HydraSigningKey <$> rawDeserialiseSignKeyDSIGN bs --- | Hydra verification key, which can be used to 'verify' signed messages. -newtype VerificationKey = HydraVerificationKey (VerKeyDSIGN SignAlg) - deriving (Eq, Show) - deriving newtype (ToCBOR, FromCBOR) +instance HasTextEnvelope (SigningKey HydraKey) where + textEnvelopeType _ = + "HydraSigningKey_" + <> fromString (algorithmNameDSIGN (Proxy :: Proxy Ed25519DSIGN)) -instance HasTypeProxy VerificationKey where - data AsType VerificationKey = AsHydraVerificationKey - proxyToAsType _ = AsHydraVerificationKey +instance Arbitrary (VerificationKey HydraKey) where + arbitrary = getVerificationKey . generateSigningKey <$> arbitrary -instance SerialiseAsRawBytes VerificationKey where +instance SerialiseAsRawBytes (VerificationKey HydraKey) where serialiseToRawBytes (HydraVerificationKey vk) = rawSerialiseVerKeyDSIGN vk - deserialiseFromRawBytes AsHydraVerificationKey bs = + deserialiseFromRawBytes (AsVerificationKey AsHydraKey) bs = HydraVerificationKey <$> rawDeserialiseVerKeyDSIGN bs -instance ToJSON VerificationKey where +instance ToJSON (VerificationKey HydraKey) where toJSON = toJSON . serialiseToRawBytesHexText -- TODO: It would be nice(r) to have a bech32 representation for verification @@ -112,7 +160,7 @@ instance ToJSON VerificationKey where -- bech32PrefixFor = const "hydra_vk" -- bech32PrefixesPermitted _ = ["hydra_vk"] -instance FromJSON VerificationKey where +instance FromJSON (VerificationKey HydraKey) where parseJSON = Aeson.withText "VerificationKey" $ decodeBase16 >=> deserialiseKey where deserialiseKey = @@ -121,29 +169,25 @@ instance FromJSON VerificationKey where (pure . HydraVerificationKey) . rawDeserialiseVerKeyDSIGN -instance Arbitrary VerificationKey where - arbitrary = deriveVerificationKey . generateSigningKey <$> arbitrary +instance HasTextEnvelope (VerificationKey HydraKey) where + textEnvelopeType _ = + "HydraVerificationKey_" + <> fromString (algorithmNameDSIGN (Proxy :: Proxy Ed25519DSIGN)) --- | Serialise the verification key material as raw bytes. -serialiseVerificationKeyToRawBytes :: VerificationKey -> ByteString -serialiseVerificationKeyToRawBytes (HydraVerificationKey vk) = rawSerialiseVerKeyDSIGN vk - --- | Deserialise a verirfication key from raw bytes. -deserialiseVerificationKeyFromRawBytes :: MonadFail m => ByteString -> m VerificationKey -deserialiseVerificationKeyFromRawBytes bytes = - case rawDeserialiseVerKeyDSIGN bytes of - Nothing -> fail "failed to deserialise verification key" - Just key -> pure $ HydraVerificationKey key - --- | Get the Blake2b hash of a 'VerificationKey'. -hashVerificationKey :: VerificationKey -> Hash Blake2b_256 VerificationKey -hashVerificationKey (HydraVerificationKey vk) = - castHash $ hashVerKeyDSIGN vk +-- | Create a new 'SigningKey' from a 'ByteString' seed. The created keys are +-- not random and insecure, so don't use this in production code! +generateSigningKey :: ByteString -> SigningKey HydraKey +generateSigningKey seed = + HydraSigningKey . genKeyDSIGN $ mkSeedFromBytes padded + where + needed = fromIntegral $ seedSizeDSIGN (Proxy :: Proxy Ed25519DSIGN) + provided = BS.length seed + padded = seed <> BS.pack (replicate (needed - provided) 0) -- * Signatures -- | Signature of 'a', not containing the actual payload. -newtype Signature a = HydraSignature (SigDSIGN SignAlg) +newtype Signature a = HydraSignature (SigDSIGN Ed25519DSIGN) deriving (Eq) deriving newtype (ToCBOR, FromCBOR) @@ -174,14 +218,19 @@ instance FromJSON a => FromJSON (Signature a) where $ rawDeserialiseSigDSIGN bs -- | Sign some value 'a' with the provided 'SigningKey'. -sign :: SignableRepresentation a => SigningKey -> a -> Signature a +sign :: SignableRepresentation a => SigningKey HydraKey -> a -> Signature a sign (HydraSigningKey sk) a = HydraSignature $ signDSIGN ctx a sk where - ctx = () :: ContextDSIGN SignAlg + ctx = () :: ContextDSIGN Ed25519DSIGN -- | Verify a given 'Signature a' and value 'a' using provided 'VerificationKey'. -verify :: SignableRepresentation a => VerificationKey -> Signature a -> a -> Bool +verify :: + SignableRepresentation a => + VerificationKey HydraKey -> + Signature a -> + a -> + Bool verify (HydraVerificationKey vk) (HydraSignature sig) a = case verifyDSIGN ctx vk a sig of Right () -> True @@ -189,7 +238,7 @@ verify (HydraVerificationKey vk) (HydraSignature sig) a = -- to distinguish in our interface Left _ -> False where - ctx = () :: ContextDSIGN SignAlg + ctx = () :: ContextDSIGN Ed25519DSIGN -- * Multi-signatures diff --git a/hydra-node/src/Hydra/HeadLogic.hs b/hydra-node/src/Hydra/HeadLogic.hs index 67e986e05ae..304b48d2128 100644 --- a/hydra-node/src/Hydra/HeadLogic.hs +++ b/hydra-node/src/Hydra/HeadLogic.hs @@ -23,7 +23,7 @@ import Hydra.Chain ( PostTxError, ) import Hydra.ClientInput (ClientInput (..)) -import Hydra.Crypto (Signature, SigningKey, aggregateInOrder, sign, verify) +import Hydra.Crypto (HydraKey, Signature, SigningKey, aggregateInOrder, sign, verify) import Hydra.Ledger ( IsTx, Ledger, @@ -191,7 +191,7 @@ data Environment = Environment party :: Party , -- NOTE(MB): In the long run we would not want to keep the signing key in -- memory, i.e. have an 'Effect' for signing or so. - signingKey :: SigningKey + signingKey :: SigningKey HydraKey , otherParties :: [Party] } diff --git a/hydra-node/src/Hydra/Network/Message.hs b/hydra-node/src/Hydra/Network/Message.hs index 3961f5e8f71..0648ed1625e 100644 --- a/hydra-node/src/Hydra/Network/Message.hs +++ b/hydra-node/src/Hydra/Network/Message.hs @@ -4,7 +4,7 @@ module Hydra.Network.Message where import Hydra.Prelude -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (Signature) import Hydra.Ledger (IsTx, UTxOType) import Hydra.Network (Host) import Hydra.Party (Party) @@ -15,7 +15,7 @@ import Hydra.Snapshot (Snapshot, SnapshotNumber) data Message tx = ReqTx {party :: Party, transaction :: tx} | ReqSn {party :: Party, snapshotNumber :: SnapshotNumber, transactions :: [tx]} - | AckSn {party :: Party, signed :: Hydra.Signature (Snapshot tx), snapshotNumber :: SnapshotNumber} + | AckSn {party :: Party, signed :: Signature (Snapshot tx), snapshotNumber :: SnapshotNumber} | Connected {peer :: Host} | Disconnected {peer :: Host} deriving stock (Generic, Eq, Show) diff --git a/hydra-node/src/Hydra/Node.hs b/hydra-node/src/Hydra/Node.hs index 704976346c3..3843cae2381 100644 --- a/hydra-node/src/Hydra/Node.hs +++ b/hydra-node/src/Hydra/Node.hs @@ -33,12 +33,10 @@ import Control.Monad.Class.MonadSTM ( writeTQueue, ) import Hydra.API.Server (Server, sendOutput) +import Hydra.Cardano.Api (AsType (AsSigningKey, AsVerificationKey), deserialiseFromRawBytes) import Hydra.Chain (Chain (..), ChainEvent, PostTxError) import Hydra.ClientInput (ClientInput) -import Hydra.Crypto ( - deserialiseSigningKeyFromRawBytes, - deserialiseVerificationKeyFromRawBytes, - ) +import Hydra.Crypto (AsType (AsHydraKey)) import Hydra.HeadLogic ( Effect (..), Environment (..), @@ -69,14 +67,18 @@ initEnvironment Options{hydraSigningKey, hydraVerificationKeys} = do , otherParties } where + -- TODO: use text envelopes instead of this maybe fail stuff loadSigningKey p = - readFileBS p >>= deserialiseSigningKeyFromRawBytes + readFileBS p >>= maybeFail <$> deserialiseFromRawBytes (AsSigningKey AsHydraKey) loadParty p = Party <$> loadVerificationKey p loadVerificationKey p = do - readFileBS p >>= deserialiseVerificationKeyFromRawBytes + readFileBS p >>= maybeFail <$> deserialiseFromRawBytes (AsVerificationKey AsHydraKey) + + maybeFail = maybe (fail "could not deserialise from raw bytes") pure + -- ** Create and run a hydra node data HydraNode tx m = HydraNode diff --git a/hydra-node/src/Hydra/Party.hs b/hydra-node/src/Hydra/Party.hs index 1c1bf0a073f..38843778a18 100644 --- a/hydra-node/src/Hydra/Party.hs +++ b/hydra-node/src/Hydra/Party.hs @@ -7,12 +7,12 @@ import Hydra.Prelude hiding (show) import Data.Aeson (ToJSONKey) import Data.Aeson.Types (FromJSONKey) -import Hydra.Crypto (hashVerificationKey) -import qualified Hydra.Crypto as Hydra +import Hydra.Cardano.Api (AsType (AsVerificationKey), SerialiseAsRawBytes (deserialiseFromRawBytes, serialiseToRawBytes), SigningKey, VerificationKey, getVerificationKey, verificationKeyHash) +import Hydra.Crypto (AsType (AsHydraKey), HydraKey) import qualified Hydra.Data.Party as OnChain -- | Identifies a party in a Hydra head by it's 'VerificationKey'. -newtype Party = Party {vkey :: Hydra.VerificationKey} +newtype Party = Party {vkey :: VerificationKey HydraKey} deriving (Eq, Show, Generic) deriving anyclass (ToJSON, FromJSON, FromJSONKey, ToJSONKey) @@ -20,7 +20,7 @@ newtype Party = Party {vkey :: Hydra.VerificationKey} -- based on Hashable? instance Ord Party where Party{vkey = a} <= Party{vkey = b} = - hashVerificationKey a <= hashVerificationKey b + verificationKeyHash a <= verificationKeyHash b instance Arbitrary Party where arbitrary = Party <$> arbitrary @@ -32,15 +32,15 @@ instance ToCBOR Party where toCBOR Party{vkey} = toCBOR vkey -- | Get the 'Party' given some Hydra 'SigningKey'. -deriveParty :: Hydra.SigningKey -> Party -deriveParty = Party . Hydra.deriveVerificationKey +deriveParty :: SigningKey HydraKey -> Party +deriveParty = Party . getVerificationKey -- | Convert "high-level" 'Party' to the "low-level" representation as used -- on-chain. See 'Hydra.Data.Party.Party' for an explanation why this is a -- distinct type. partyToChain :: Party -> OnChain.Party partyToChain Party{vkey} = - OnChain.partyFromVerificationKeyBytes $ Hydra.serialiseVerificationKeyToRawBytes vkey + OnChain.partyFromVerificationKeyBytes $ serialiseToRawBytes vkey -- | Retrieve the "high-level" 'Party from the "low-level" on-chain -- representation. This can fail because of the lower type-safety used on-chain @@ -48,4 +48,6 @@ partyToChain Party{vkey} = -- for an explanation why this is a distinct type. partyFromChain :: MonadFail m => OnChain.Party -> m Party partyFromChain = - fmap Party . Hydra.deserialiseVerificationKeyFromRawBytes . OnChain.partyToVerficationKeyBytes + maybe (fail "partyFromChain got Nothing") (pure . Party) + . deserialiseFromRawBytes (AsVerificationKey AsHydraKey) + . OnChain.partyToVerficationKeyBytes diff --git a/hydra-node/src/Hydra/ServerOutput.hs b/hydra-node/src/Hydra/ServerOutput.hs index 496ee869905..6c650cfc12d 100644 --- a/hydra-node/src/Hydra/ServerOutput.hs +++ b/hydra-node/src/Hydra/ServerOutput.hs @@ -4,7 +4,7 @@ module Hydra.ServerOutput where import Hydra.Chain (PostChainTx, PostTxError) import Hydra.ClientInput (ClientInput (..)) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (MultiSignature) import Hydra.Ledger (IsTx, UTxOType, ValidationError) import Hydra.Network (Host) import Hydra.Party (Party) @@ -28,7 +28,7 @@ data ServerOutput tx | TxInvalid {utxo :: UTxOType tx, transaction :: tx, validationError :: ValidationError} | SnapshotConfirmed { snapshot :: Snapshot tx - , signatures :: Hydra.MultiSignature (Snapshot tx) + , signatures :: MultiSignature (Snapshot tx) } | GetUTxOResponse {utxo :: UTxOType tx} | InvalidInput {reason :: String, input :: Text} diff --git a/hydra-node/src/Hydra/Snapshot.hs b/hydra-node/src/Hydra/Snapshot.hs index 7df846d44be..3b70521bc8a 100644 --- a/hydra-node/src/Hydra/Snapshot.hs +++ b/hydra-node/src/Hydra/Snapshot.hs @@ -8,7 +8,8 @@ import Hydra.Prelude import Cardano.Crypto.Util (SignableRepresentation (..)) import Codec.Serialise (serialise) import Data.Aeson (object, withObject, (.:), (.=)) -import qualified Hydra.Crypto as Hydra +import Hydra.Cardano.Api (SigningKey) +import Hydra.Crypto (HydraKey, MultiSignature, aggregate, generateSigningKey, sign) import Hydra.Ledger (IsTx (..)) import Plutus.V2.Ledger.Api (toBuiltin, toData) import Test.QuickCheck (frequency, suchThat) @@ -74,7 +75,7 @@ data ConfirmedSnapshot tx } | ConfirmedSnapshot { snapshot :: Snapshot tx - , signatures :: Hydra.MultiSignature (Snapshot tx) + , signatures :: MultiSignature (Snapshot tx) } deriving (Generic, Eq, Show, ToJSON, FromJSON) @@ -99,7 +100,7 @@ isInitialSnapshot = \case instance IsTx tx => Arbitrary (ConfirmedSnapshot tx) where arbitrary = do - ks <- fmap Hydra.generateSigningKey <$> arbitrary + ks <- fmap generateSigningKey <$> arbitrary utxo <- arbitrary genConfirmedSnapshot 0 utxo ks @@ -111,7 +112,7 @@ genConfirmedSnapshot :: -- this lower bound. SnapshotNumber -> UTxOType tx -> - [Hydra.SigningKey] -> + [SigningKey HydraKey] -> Gen (ConfirmedSnapshot tx) genConfirmedSnapshot minSn utxo sks | minSn > 0 = confirmedSnapshot @@ -141,5 +142,5 @@ genConfirmedSnapshot minSn utxo sks -- snapshots number <- arbitrary `suchThat` (> minSn) let snapshot = Snapshot{number, utxo, confirmed = []} - let signatures = Hydra.aggregate $ fmap (`Hydra.sign` snapshot) sks + let signatures = aggregate $ fmap (`sign` snapshot) sks pure $ ConfirmedSnapshot{snapshot, signatures} diff --git a/hydra-node/test/Hydra/BehaviorSpec.hs b/hydra-node/test/Hydra/BehaviorSpec.hs index b206b75cdf7..fdbcbeb25d6 100644 --- a/hydra-node/test/Hydra/BehaviorSpec.hs +++ b/hydra-node/test/Hydra/BehaviorSpec.hs @@ -21,11 +21,11 @@ import Control.Monad.Class.MonadTimer (timeout) import Control.Monad.IOSim (Failure (FailureDeadlock), IOSim, runSimTrace, selectTraceEventsDynamic) import GHC.Records (getField) import Hydra.API.Server (Server (..)) +import Hydra.Cardano.Api (SigningKey) import Hydra.Chain (Chain (..), ChainEvent (..), HeadParameters (..), OnChainTx (..), PostChainTx (..)) import Hydra.ClientInput import Hydra.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod), toNominalDiffTime) -import Hydra.Crypto (aggregate, sign) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, aggregate, sign) import Hydra.HeadLogic ( Effect (ClientEffect), Environment (..), @@ -536,7 +536,7 @@ nothingHappensFor node secs = withHydraNode :: forall s a. - Hydra.SigningKey -> + SigningKey HydraKey -> [Party] -> ConnectToChain SimpleTx (IOSim s) -> (TestHydraNode SimpleTx (IOSim s) -> IOSim s a) -> @@ -575,7 +575,7 @@ createTestHydraNode outputs outputHistory node ConnectToChain{history} = createHydraNode :: (MonadDelay m, MonadAsync m) => Ledger tx -> - Hydra.SigningKey -> + SigningKey HydraKey -> [Party] -> TQueue m (ServerOutput tx) -> TVar m [ServerOutput tx] -> diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs index e59564fa163..e78b42dccbe 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Close.hs @@ -14,8 +14,7 @@ import Hydra.Chain.Direct.Contract.Mutation (Mutation (..), SomeMutation (..), c import Hydra.Chain.Direct.Fixture (genForParty, testNetworkId, testPolicyId) import Hydra.Chain.Direct.Tx (ClosingSnapshot (..), OpenThreadOutput (..), assetNameFromVerificationKey, closeTx, mkHeadOutput) import qualified Hydra.Contract.HeadState as Head -import Hydra.Crypto (MultiSignature, aggregate, sign, toPlutusSignatures) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, MultiSignature, aggregate, sign, toPlutusSignatures) import qualified Hydra.Data.ContestationPeriod as OnChain import qualified Hydra.Data.Party as OnChain import Hydra.Ledger (hashUTxO) @@ -122,7 +121,7 @@ somePartyCardanoVerificationKey :: VerificationKey PaymentKey somePartyCardanoVerificationKey = flip generateWith 42 $ do genForParty genVerificationKey <$> elements healthyParties -healthySigningKeys :: [Hydra.SigningKey] +healthySigningKeys :: [SigningKey HydraKey] healthySigningKeys = [aliceSk, bobSk, carolSk] healthyParties :: [Party] @@ -131,7 +130,7 @@ healthyParties = deriveParty <$> healthySigningKeys healthyOnChainParties :: [OnChain.Party] healthyOnChainParties = partyToChain <$> healthyParties -healthySignature :: SnapshotNumber -> Hydra.MultiSignature (Snapshot Tx) +healthySignature :: SnapshotNumber -> MultiSignature (Snapshot Tx) healthySignature number = aggregate [sign sk snapshot | sk <- healthySigningKeys] where snapshot = healthySnapshot{number} diff --git a/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs b/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs index 98ae102b777..382cace83ce 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs @@ -19,8 +19,7 @@ import Hydra.Chain.Direct.Contract.Mutation ( import Hydra.Chain.Direct.Fixture (genForParty, testNetworkId, testPolicyId) import Hydra.Chain.Direct.Tx (ClosedThreadOutput (..), assetNameFromVerificationKey, contestTx, mkHeadOutput) import qualified Hydra.Contract.HeadState as Head -import Hydra.Crypto (aggregate, sign, toPlutusSignatures) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, MultiSignature, aggregate, sign, toPlutusSignatures) import qualified Hydra.Data.Party as OnChain import Hydra.Ledger (hashUTxO) import Hydra.Ledger.Cardano (genOneUTxOFor, genVerificationKey) @@ -138,7 +137,7 @@ somePartyCardanoVerificationKey :: VerificationKey PaymentKey somePartyCardanoVerificationKey = flip generateWith 42 $ do genForParty genVerificationKey <$> elements healthyParties -healthySigningKeys :: [Hydra.SigningKey] +healthySigningKeys :: [SigningKey HydraKey] healthySigningKeys = [aliceSk, bobSk, carolSk] healthyParties :: [Party] @@ -147,7 +146,7 @@ healthyParties = deriveParty <$> healthySigningKeys healthyOnChainParties :: [OnChain.Party] healthyOnChainParties = partyToChain <$> healthyParties -healthySignature :: SnapshotNumber -> Hydra.MultiSignature (Snapshot Tx) +healthySignature :: SnapshotNumber -> MultiSignature (Snapshot Tx) healthySignature number = aggregate [sign sk snapshot | sk <- healthySigningKeys] where @@ -177,7 +176,7 @@ genContestMutation ) = oneof [ SomeMutation MutateSignatureButNotSnapshotNumber . ChangeHeadRedeemer <$> do - mutatedSignature <- arbitrary :: Gen (Hydra.MultiSignature (Snapshot Tx)) + mutatedSignature <- arbitrary :: Gen (MultiSignature (Snapshot Tx)) pure $ Head.Contest { snapshotNumber = toInteger healthyContestSnapshotNumber diff --git a/hydra-node/test/Hydra/Chain/Direct/ContractSpec.hs b/hydra-node/test/Hydra/Chain/Direct/ContractSpec.hs index bf168dbe7ba..3bad53e2680 100644 --- a/hydra-node/test/Hydra/Chain/Direct/ContractSpec.hs +++ b/hydra-node/test/Hydra/Chain/Direct/ContractSpec.hs @@ -38,8 +38,7 @@ import Hydra.Contract.Head ( verifySnapshotSignature, ) import qualified Hydra.Contract.Head as OnChain -import Hydra.Crypto (aggregate, sign, toPlutusSignatures) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (aggregate, generateSigningKey, sign, toPlutusSignatures) import Hydra.Ledger (hashUTxO) import qualified Hydra.Ledger as OffChain import Hydra.Ledger.Cardano ( @@ -182,8 +181,8 @@ prop_verifyOffChainSignatures :: Property prop_verifyOffChainSignatures = forAll arbitrary $ \(snapshot@Snapshot{number, utxo} :: Snapshot SimpleTx) -> forAll arbitrary $ \seed -> - let sk = Hydra.generateSigningKey seed - offChainSig = Hydra.sign sk snapshot + let sk = generateSigningKey seed + offChainSig = sign sk snapshot onChainSig = List.head . toPlutusSignatures $ aggregate [offChainSig] onChainParty = partyToChain $ deriveParty sk snapshotNumber = toInteger number diff --git a/hydra-node/test/Hydra/Chain/Direct/Fixture.hs b/hydra-node/test/Hydra/Chain/Direct/Fixture.hs index 8b3fcdddbe5..456f0146d24 100644 --- a/hydra-node/test/Hydra/Chain/Direct/Fixture.hs +++ b/hydra-node/test/Hydra/Chain/Direct/Fixture.hs @@ -25,9 +25,10 @@ import Hydra.Cardano.Api ( PolicyId, SlotNo (..), TxIn, + verificationKeyHash, ) import Hydra.Chain.Direct.Tx (headPolicyId) -import Hydra.Crypto (hashVerificationKey) +import Hydra.Crypto (Hash (HydraKeyHash)) import Hydra.Ledger.Cardano.Evaluate (pparams) import Hydra.Party (Party (..)) import Test.Cardano.Ledger.Alonzo.Serialisation.Generators () @@ -46,8 +47,10 @@ genForParty gen Party{vkey} = seed = fromIntegral . uintegerFromBytes - . hashToBytes - $ hashVerificationKey vkey + . hydraKeyHashToBytes + $ verificationKeyHash vkey + + hydraKeyHashToBytes (HydraKeyHash h) = hashToBytes h -- * Cardano tx utilities diff --git a/hydra-node/test/Hydra/CryptoSpec.hs b/hydra-node/test/Hydra/CryptoSpec.hs index 1bd02e5959b..f0fcedf60ca 100644 --- a/hydra-node/test/Hydra/CryptoSpec.hs +++ b/hydra-node/test/Hydra/CryptoSpec.hs @@ -33,9 +33,9 @@ specVerificationKey :: Spec specVerificationKey = describe "VerificationKey" $ do it "show includes escaped hex" $ - show (deriveVerificationKey $ generateSigningKey "alice") `shouldContain` "ce1da235714466fc7" + show (getVerificationKey $ generateSigningKey "alice") `shouldContain` "ce1da235714466fc7" - roundtripAndGoldenSpecs (Proxy @VerificationKey) + roundtripAndGoldenSpecs (Proxy @(VerificationKey HydraKey)) specSignature :: Spec specSignature = @@ -47,7 +47,7 @@ specSignature = ==> sign sk msgA =/= sign sk msgB prop "sign/verify roundtrip" $ \sk (msg :: ByteString) -> let sig = sign sk msg - in verify (deriveVerificationKey sk) sig msg + in verify (getVerificationKey sk) sig msg & counterexample (show sig) specMultiSignature :: Spec diff --git a/hydra-node/test/Hydra/Model.hs b/hydra-node/test/Hydra/Model.hs index 840784e45ea..4a4655457a6 100644 --- a/hydra-node/test/Hydra/Model.hs +++ b/hydra-node/test/Hydra/Model.hs @@ -46,7 +46,7 @@ import Hydra.Chain (HeadParameters (..)) import Hydra.Chain.Direct.Fixture (defaultGlobals, defaultLedgerEnv, testNetworkId) import Hydra.ClientInput (ClientInput (NewTx)) import qualified Hydra.ClientInput as Input -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey) import Hydra.HeadLogic (Committed, PendingCommits) import Hydra.Ledger (IsTx (..)) import Hydra.Ledger.Cardano (cardanoLedger, genAdaValue, genKeyPair, genSigningKey, mkSimpleTx) @@ -117,7 +117,7 @@ data OffChainState = OffChainState data WorldState (m :: Type -> Type) = WorldState { -- |List of parties identified by both signing keys required to run protocol. -- This list must not contain any duplicated key. - hydraParties :: [(Hydra.SigningKey, CardanoSigningKey)] + hydraParties :: [(SigningKey HydraKey, CardanoSigningKey)] , hydraState :: GlobalState } deriving (Eq, Show) @@ -229,7 +229,7 @@ instance data Action (WorldState m) a where -- | Creation of the world. Seed :: - { seedKeys :: [(Hydra.SigningKey, CardanoSigningKey)] + { seedKeys :: [(SigningKey HydraKey, CardanoSigningKey)] } -> Action (WorldState m) () -- | All other actions are simply `ClientInput` from some `Party`. @@ -440,7 +440,7 @@ seedWorld :: , MonadAsync m , MonadCatch m ) => - [(Hydra.SigningKey, b)] -> + [(SigningKey HydraKey, b)] -> ActionMonad (WorldState m) () seedWorld seedKeys = do let parties = map (deriveParty . fst) seedKeys @@ -568,7 +568,7 @@ unsafeConstructorName = Prelude.head . Prelude.words . show -- |Generate a list of pairs of Hydra/Cardano signing keys. -- All the keys in this list are guaranteed to be unique. -partyKeys :: Gen [(Hydra.SigningKey, CardanoSigningKey)] +partyKeys :: Gen [(SigningKey HydraKey, CardanoSigningKey)] partyKeys = sized $ \len -> do hks <- nub <$> vectorOf len arbitrary diff --git a/hydra-node/test/Hydra/NodeSpec.hs b/hydra-node/test/Hydra/NodeSpec.hs index 0f907815e70..c018ed17dd3 100644 --- a/hydra-node/test/Hydra/NodeSpec.hs +++ b/hydra-node/test/Hydra/NodeSpec.hs @@ -6,6 +6,7 @@ import Hydra.Prelude import Test.Hydra.Prelude import Hydra.API.Server (Server (..)) +import Hydra.Cardano.Api (SigningKey) import Hydra.Chain ( Chain (..), ChainEvent (Observation), @@ -15,8 +16,7 @@ import Hydra.Chain ( PostTxError (NoSeedInput), ) import Hydra.ClientInput (ClientInput (..)) -import Hydra.Crypto (sign) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, sign) import Hydra.HeadLogic ( Environment (..), Event (..), @@ -138,7 +138,7 @@ runToCompletion tracer node@HydraNode{eq = EventQueue{isEmpty}} = go createHydraNode :: (MonadSTM m, MonadDelay m, MonadAsync m) => - Hydra.SigningKey -> + SigningKey HydraKey -> [Party] -> [Event SimpleTx] -> m (HydraNode SimpleTx m) diff --git a/hydra-node/test/Test/Hydra/Fixture.hs b/hydra-node/test/Test/Hydra/Fixture.hs index f26125294f2..088bf0bf504 100644 --- a/hydra-node/test/Test/Hydra/Fixture.hs +++ b/hydra-node/test/Test/Hydra/Fixture.hs @@ -1,11 +1,9 @@ -{-# OPTIONS_GHC -Wno-orphans #-} - -- | Test and example values used across hydra-node tests. module Test.Hydra.Fixture where +import Hydra.Cardano.Api (SigningKey, VerificationKey, getVerificationKey) import Hydra.ContestationPeriod (ContestationPeriod (..)) -import Hydra.Crypto (deriveVerificationKey, generateSigningKey) -import qualified Hydra.Crypto as Hydra +import Hydra.Crypto (HydraKey, generateSigningKey) import Hydra.Party (Party, deriveParty) alice, bob, carol :: Party @@ -13,15 +11,15 @@ alice = deriveParty aliceSk bob = deriveParty bobSk carol = deriveParty carolSk -aliceSk, bobSk, carolSk :: Hydra.SigningKey +aliceSk, bobSk, carolSk :: SigningKey HydraKey aliceSk = generateSigningKey "alice" bobSk = generateSigningKey "bob" carolSk = generateSigningKey "carol" -aliceVk, bobVk, carolVk :: Hydra.VerificationKey -aliceVk = deriveVerificationKey aliceSk -bobVk = deriveVerificationKey bobSk -carolVk = deriveVerificationKey carolSk +aliceVk, bobVk, carolVk :: VerificationKey HydraKey +aliceVk = getVerificationKey aliceSk +bobVk = getVerificationKey bobSk +carolVk = getVerificationKey carolSk cperiod :: ContestationPeriod cperiod = UnsafeContestationPeriod 42 diff --git a/shell.nix b/shell.nix index 18f75bc7fdc..41f64479067 100644 --- a/shell.nix +++ b/shell.nix @@ -18,8 +18,8 @@ let cardano-node = import (pkgs.fetchgit { url = "https://github.com/input-output-hk/cardano-node"; - rev = "1.35.0"; - sha256 = "06arx9hv7dn3qxfy83f0b6018rxbsvh841nvfyg5w6qclm1hddj7"; + rev = "1.35.3-testnetonly"; + sha256 = "0vg5775z683wf421asxjm7g2b6yxmgprpylhs9ryb035id83slp2"; }) { };