From 73a656881ca0be594ba457c490bf8c76042df99e Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Mon, 8 Jan 2024 17:20:46 +0100 Subject: [PATCH 01/11] Add /protocol-parameters schema test and draft validateJSON function Draft a test which checks the schema of the /protocol-parameters endpoint response using a re-usable validateJSON function. The function signature is kept similar to [openapi3](https://hackage.haskell.org/package/openapi3-3.2.4/docs/Data-OpenApi-Schema-Validation.html#v:validateJSON) to allow migration to an openapi 'Schema' later. --- hydra-node/test/Hydra/API/HTTPServerSpec.hs | 40 ++++++++++++++------- hydra-node/test/Hydra/JSONSchema.hs | 30 ++++++++++++++-- 2 files changed, 54 insertions(+), 16 deletions(-) diff --git a/hydra-node/test/Hydra/API/HTTPServerSpec.hs b/hydra-node/test/Hydra/API/HTTPServerSpec.hs index 4f139fcd784..23e2deb2b01 100644 --- a/hydra-node/test/Hydra/API/HTTPServerSpec.hs +++ b/hydra-node/test/Hydra/API/HTTPServerSpec.hs @@ -4,7 +4,7 @@ import Hydra.Prelude hiding (get) import Test.Hydra.Prelude import Cardano.Binary (serialize') -import Data.Aeson (Result (Error, Success), Value (String), encode, fromJSON) +import Data.Aeson (Result (Error, Success), Value (String), decode, encode, fromJSON) import Data.Aeson.Lens (key, nth) import Data.ByteString.Base16 qualified as Base16 import Hydra.API.HTTPServer (DraftCommitTxRequest, DraftCommitTxResponse, SubmitTxRequest (..), TransactionSubmitted, httpApp) @@ -12,9 +12,10 @@ import Hydra.API.ServerSpec (dummyChainHandle) import Hydra.Cardano.Api (serialiseToTextEnvelope, toLedgerTx) import Hydra.Chain.Direct.Fixture (defaultPParams) import Hydra.Chain.Direct.State () -import Hydra.JSONSchema (prop_validateJSONSchema) +import Hydra.JSONSchema (prop_validateJSONSchema, validateJSON, withJsonSpecifications) import Hydra.Ledger.Cardano (Tx) import Hydra.Logging (nullTracer) +import System.FilePath (()) import Test.Aeson.GenericSpecs (roundtripAndGoldenSpecs) import Test.Hspec.Wai (MatchBody (..), ResponseMatcher (matchBody), get, shouldRespondWith, with) import Test.QuickCheck.Property (counterexample, forAll, property, withMaxSuccess) @@ -87,17 +88,30 @@ apiServerSpec :: Spec apiServerSpec = do with (return webServer) $ do describe "API should respond correctly" $ - it "GET /protocol-parameters works" $ - get "/protocol-parameters" - `shouldRespondWith` 200 - { matchBody = - MatchBody - ( \_ actualBody -> - if actualBody /= encode defaultPParams - then Just "Request body missmatch" - else Nothing - ) - } + describe "GET /protocol-parameters" $ do + it "matches schema" $ + withJsonSpecifications $ \schemaDir -> do + get "/protocol-parameters" + `shouldRespondWith` 200 + { matchBody = MatchBody $ \_ actualBody -> + decode actualBody + >>= validateJSON + (schemaDir "api.json") + (key "components" . key "messages" . key "ProtocolParameters") + } + + it "responds given parameters" $ + get "/protocol-parameters" + `shouldRespondWith` 200 + { matchBody = matchJSON defaultPParams + } where webServer = httpApp nullTracer dummyChainHandle defaultPParams getHeadId getHeadId = pure Nothing + +-- * Helpers + +-- | Create a 'ResponseMatcher' or 'MatchBody' from a JSON serializable value +-- (using their 'IsString' instances). +matchJSON :: (IsString s, ToJSON a) => a -> s +matchJSON = fromString . decodeUtf8 . encode diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/test/Hydra/JSONSchema.hs index 61969cd92f4..97b060acc65 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/test/Hydra/JSONSchema.hs @@ -6,7 +6,7 @@ import Hydra.Prelude import Control.Arrow (left) import Control.Lens (Traversal', at, (?~), (^..), (^?)) -import Data.Aeson ((.=)) +import Data.Aeson (Value, (.=)) import Data.Aeson qualified as Aeson import Data.Aeson.Lens (key, _Array, _String) import Data.List qualified as List @@ -27,7 +27,19 @@ import Test.QuickCheck (Property, counterexample, forAllShrink, resize, vectorOf import Test.QuickCheck.Monadic (assert, monadicIO, monitor, run) import Prelude qualified --- | Validate an 'Arbitrary' value against a JSON schema. +-- | A schema validation error (like +-- Data.OpenApi.Schema.Validation.ValidationError interface). +type ValidationError = String + +-- | Validate a specific JSON value against a given JSON schema. +-- +-- The path to the schema must be a fully qualified path to .json schema file. +-- Use 'withJsonSpecifications' to convert hydra-specific yaml schemas into +-- proper json schemas, for example: +-- +-- @@ +-- withJsonSpecifications $ \dir -> validateJSON (dir "api.json") id Null +-- @@ -- -- The second argument is a lens that says which part of the JSON file to use to -- do the validation, for example: @@ -38,11 +50,23 @@ import Prelude qualified -- -- which selects the JSON schema for "Address" types in a bigger specification, -- say an asyncapi description. +validateJSON :: + -- | Path to the JSON file holding the schema. + FilePath -> + -- | Selector into the JSON file pointing to the schema to be validated. + SpecificationSelector -> + Value -> + Maybe ValidationError +validateJSON schemaFilePath selector value = Just "not implemented" + +-- | Validate an 'Arbitrary' value against a JSON schema. +-- +-- See 'validateJSON' for how to provide a selector. prop_validateJSONSchema :: forall a. (ToJSON a, Arbitrary a, Show a) => -- | Path to the JSON file holding the schema. - String -> + FilePath -> -- | Selector into the JSON file pointing to the schema to be validated. SpecificationSelector -> Property From 17a7f8af7d87fb785a438c5178daf71142879939 Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Mon, 8 Jan 2024 18:44:51 +0100 Subject: [PATCH 02/11] Expand and test validateJSON utility --- hydra-node/hydra-node.cabal | 2 + hydra-node/test/Hydra/API/HTTPServerSpec.hs | 3 +- hydra-node/test/Hydra/JSONSchema.hs | 64 +++++++++++++++++---- hydra-node/test/Hydra/JSONSchemaSpec.hs | 61 ++++++++++++++++++++ 4 files changed, 118 insertions(+), 12 deletions(-) create mode 100644 hydra-node/test/Hydra/JSONSchemaSpec.hs diff --git a/hydra-node/hydra-node.cabal b/hydra-node/hydra-node.cabal index d070c7db627..e5cb1f12148 100644 --- a/hydra-node/hydra-node.cabal +++ b/hydra-node/hydra-node.cabal @@ -275,6 +275,7 @@ test-suite tests Hydra.HeadLogicSnapshotSpec Hydra.HeadLogicSpec Hydra.JSONSchema + Hydra.JSONSchemaSpec Hydra.Ledger.Cardano.TimeSpec Hydra.Ledger.CardanoSpec Hydra.Ledger.SimpleSpec @@ -354,6 +355,7 @@ test-suite tests , typed-protocols-examples >=0.1.0.0 , vector , versions + , wai-extra , websockets , yaml diff --git a/hydra-node/test/Hydra/API/HTTPServerSpec.hs b/hydra-node/test/Hydra/API/HTTPServerSpec.hs index 23e2deb2b01..2968e8e5e24 100644 --- a/hydra-node/test/Hydra/API/HTTPServerSpec.hs +++ b/hydra-node/test/Hydra/API/HTTPServerSpec.hs @@ -11,7 +11,6 @@ import Hydra.API.HTTPServer (DraftCommitTxRequest, DraftCommitTxResponse, Submit import Hydra.API.ServerSpec (dummyChainHandle) import Hydra.Cardano.Api (serialiseToTextEnvelope, toLedgerTx) import Hydra.Chain.Direct.Fixture (defaultPParams) -import Hydra.Chain.Direct.State () import Hydra.JSONSchema (prop_validateJSONSchema, validateJSON, withJsonSpecifications) import Hydra.Ledger.Cardano (Tx) import Hydra.Logging (nullTracer) @@ -97,7 +96,7 @@ apiServerSpec = do decode actualBody >>= validateJSON (schemaDir "api.json") - (key "components" . key "messages" . key "ProtocolParameters") + (key "components" . key "messages" . key "ProtocolParameters" . key "payload") } it "responds given parameters" $ diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/test/Hydra/JSONSchema.hs index 97b060acc65..ea5f24bc5f6 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/test/Hydra/JSONSchema.hs @@ -1,10 +1,14 @@ {-# LANGUAGE AllowAmbiguousTypes #-} +{-# LANGUAGE OverloadedStrings #-} +-- | Test utilities to work with JSON schemas. module Hydra.JSONSchema where import Hydra.Prelude +import Test.Hydra.Prelude import Control.Arrow (left) +import Control.Exception (IOException) import Control.Lens (Traversal', at, (?~), (^..), (^?)) import Data.Aeson (Value, (.=)) import Data.Aeson qualified as Aeson @@ -12,17 +16,15 @@ import Data.Aeson.Lens (key, _Array, _String) import Data.List qualified as List import Data.Map.Strict qualified as Map import Data.Text (pack) -import Data.Text qualified as Text import Data.Versions (SemVer (SemVer), prettySemVer, semver) import Data.Yaml qualified as Yaml -import GHC.IO.Exception (IOErrorType (OtherError)) import Paths_hydra_node qualified as Pkg import System.Directory (listDirectory) import System.Exit (ExitCode (..)) import System.FilePath (normalise, takeBaseName, takeExtension, (<.>), ()) -import System.IO.Error (IOError, ioeGetErrorType) +import System.IO.Error (IOError, isDoesNotExistError) +import System.IO.Unsafe (unsafePerformIO) import System.Process (readProcessWithExitCode) -import Test.Hydra.Prelude (failure, withTempDir) import Test.QuickCheck (Property, counterexample, forAllShrink, resize, vectorOf) import Test.QuickCheck.Monadic (assert, monadicIO, monitor, run) import Prelude qualified @@ -57,7 +59,49 @@ validateJSON :: SpecificationSelector -> Value -> Maybe ValidationError -validateJSON schemaFilePath selector value = Just "not implemented" +validateJSON schemaFilePath selector value = + -- NOTE: Use unsafePerformIO to create a pure API for testing API responses + -- around actually calling an external program to verify the schema. This is + -- fine, because the call is referentially transparent and any given + -- invocation of schema file, selector and value will always yield the same + -- result and can be shared. + unsafePerformIO + . handle anyIOExceptions + -- NOTE: We exit out of the do block deliberately using exceptions to retain + -- the temp directory for debugging (see 'withTempDir') + . handle convertFailure + . withTempDir "validateJSON" + $ \tmpDir -> do + ensureSystemRequirements + let jsonInput = tmpDir "jsonInput" + let jsonSchema = tmpDir "jsonSchema" + Aeson.eitherDecodeFileStrict schemaFilePath >>= \case + Left err -> fail $ "Failed to decode JSON schema " <> show schemaFilePath <> ": " <> err + Right schemaValue -> do + let jsonSpecSchema = + schemaValue ^? selector + <&> addField "$id" ("file://" <> tmpDir <> "/") + writeFileLBS jsonInput (Aeson.encode value) + writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) + (exitCode, out, err) <- + readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] "" + when (exitCode /= ExitSuccess) $ + failure $ + "exit code: " + <> show exitCode + <> "\n" + <> "stderr: " + <> err + <> "\n" + <> "stdout: " + <> out + pure Nothing + where + anyIOExceptions :: IOException -> IO (Maybe ValidationError) + anyIOExceptions e = pure . Just $ "IOException: " <> show e + + convertFailure :: SomeException -> IO (Maybe ValidationError) + convertFailure = pure . Just . displayException -- | Validate an 'Arbitrary' value against a JSON schema. -- @@ -201,16 +245,16 @@ addField k v = withObject (at k ?~ toJSON v) Aeson.Object m -> Aeson.Object (fn m) x -> x --- | Make sure that the required `check-jsonschema` tool is available on the system. --- Mark a test as pending when not available. +-- | Check that the required `check-jsonschema` tool is available on the system. +-- Raises an IOException (user error via 'fail') if not found or wrong version. ensureSystemRequirements :: IO () ensureSystemRequirements = getToolVersion >>= \case Right semVer -> unless (semVer >= SemVer 0 21 0 Nothing Nothing) $ - failure . Text.unpack $ + fail . toString $ "check-jsonschema version " <> prettySemVer semVer <> " found but >= 0.21.0 needed" - Left errorMsg -> failure errorMsg + Left errorMsg -> fail errorMsg where getToolVersion :: IO (Either String SemVer) getToolVersion = do @@ -219,7 +263,7 @@ ensureSystemRequirements = Right (exitCode, out, _) -> pure (List.last (List.words out) <$ if exitCode == ExitSuccess then pure () else Left "") Left (err :: IOError) - | ioeGetErrorType err == OtherError -> + | isDoesNotExistError err -> pure (Left "Make sure check-jsonschema is installed and in $PATH") Left err -> pure (Left $ show err) pure $ do diff --git a/hydra-node/test/Hydra/JSONSchemaSpec.hs b/hydra-node/test/Hydra/JSONSchemaSpec.hs new file mode 100644 index 00000000000..b6538761af5 --- /dev/null +++ b/hydra-node/test/Hydra/JSONSchemaSpec.hs @@ -0,0 +1,61 @@ +-- | Tests our JSON schema test utilities. +module Hydra.JSONSchemaSpec where + +import Hydra.Prelude +import Test.Hydra.Prelude + +import Data.Aeson (Value (..), object, (.=)) +import Data.Aeson.Lens (key) +import Data.Text (isInfixOf) +import Hydra.JSONSchema (validateJSON, withJsonSpecifications) +import System.Environment (getEnv, setEnv) +import System.FilePath (()) + +spec :: Spec +spec = + describe "validateJSON withJsonSpecifications" $ do + it "works using identity selector and Null input" $ + withJsonSpecifications $ \dir -> + validateJSON (dir "api.json") id Null + `shouldBe` Nothing + + it "fails on non-existing schema file" $ + validateJSON ("does-not-exist.json") id Null + `shouldSatisfy` \case + Just err -> "does-not-exist.json" `isInfixOf` toText err + Nothing -> False + + it "fails with missing tool" $ do + withClearedPATH $ + validateJSON ("does-not-matter.json") id Null + `shouldSatisfy` \case + Just err -> "installed" `isInfixOf` toText err + Nothing -> False + + it "selects a sub-schema correctly" $ + withJsonSpecifications $ \dir -> + validateJSON + (dir "api.json") + (key "components" . key "schemas" . key "HeadId") + (String "some-head-id") + `shouldBe` Nothing + + it "produces helpful errors" $ + withJsonSpecifications $ \dir -> + validateJSON + (dir "api.json") + (key "components" . key "schemas" . key "HeadId") + (object ["foo" .= String "bar"]) + `shouldSatisfy` \case + Just err -> "{'foo': 'bar'} is not of type 'string'" `isInfixOf` toText err + Nothing -> False + +-- | Clear PATH environment variable while executing given action. +withClearedPATH :: IO () -> IO () +withClearedPATH act = + bracket capture (setEnv "PATH") (const act) + where + capture = do + env <- getEnv "PATH" + setEnv "PATH" "" + pure env From c8cfccdf4dc38408a9dcb136eb7f2bc296248cf5 Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Mon, 8 Jan 2024 19:38:48 +0100 Subject: [PATCH 03/11] Restructure composition of validateJSON and HTTPServerSpec --- hydra-node/test/Hydra/API/HTTPServerSpec.hs | 33 ++++++-- hydra-node/test/Hydra/JSONSchema.hs | 87 ++++++++------------- hydra-node/test/Hydra/JSONSchemaSpec.hs | 28 ++----- hydra-test-utils/src/Test/Hydra/Prelude.hs | 26 +++++- 4 files changed, 86 insertions(+), 88 deletions(-) diff --git a/hydra-node/test/Hydra/API/HTTPServerSpec.hs b/hydra-node/test/Hydra/API/HTTPServerSpec.hs index 2968e8e5e24..5b665969d61 100644 --- a/hydra-node/test/Hydra/API/HTTPServerSpec.hs +++ b/hydra-node/test/Hydra/API/HTTPServerSpec.hs @@ -4,17 +4,18 @@ import Hydra.Prelude hiding (get) import Test.Hydra.Prelude import Cardano.Binary (serialize') -import Data.Aeson (Result (Error, Success), Value (String), decode, encode, fromJSON) +import Data.Aeson (Result (Error, Success), Value (String), eitherDecode, encode, fromJSON) import Data.Aeson.Lens (key, nth) import Data.ByteString.Base16 qualified as Base16 import Hydra.API.HTTPServer (DraftCommitTxRequest, DraftCommitTxResponse, SubmitTxRequest (..), TransactionSubmitted, httpApp) import Hydra.API.ServerSpec (dummyChainHandle) import Hydra.Cardano.Api (serialiseToTextEnvelope, toLedgerTx) import Hydra.Chain.Direct.Fixture (defaultPParams) -import Hydra.JSONSchema (prop_validateJSONSchema, validateJSON, withJsonSpecifications) +import Hydra.JSONSchema (SchemaSelector, prop_validateJSONSchema, validateJSON, withJsonSpecifications) import Hydra.Ledger.Cardano (Tx) import Hydra.Logging (nullTracer) import System.FilePath (()) +import System.IO.Unsafe (unsafePerformIO) import Test.Aeson.GenericSpecs (roundtripAndGoldenSpecs) import Test.Hspec.Wai (MatchBody (..), ResponseMatcher (matchBody), get, shouldRespondWith, with) import Test.QuickCheck.Property (counterexample, forAll, property, withMaxSuccess) @@ -92,11 +93,10 @@ apiServerSpec = do withJsonSpecifications $ \schemaDir -> do get "/protocol-parameters" `shouldRespondWith` 200 - { matchBody = MatchBody $ \_ actualBody -> - decode actualBody - >>= validateJSON - (schemaDir "api.json") - (key "components" . key "messages" . key "ProtocolParameters" . key "payload") + { matchBody = + matchValidJSON + (schemaDir "api.json") + (key "components" . key "messages" . key "ProtocolParameters" . key "payload") } it "responds given parameters" $ @@ -114,3 +114,22 @@ apiServerSpec = do -- (using their 'IsString' instances). matchJSON :: (IsString s, ToJSON a) => a -> s matchJSON = fromString . decodeUtf8 . encode + +-- | Create a 'MatchBody' that validates the returned JSON response against a +-- schema. NOTE: This raises impure exceptions, so only use it in this test +-- suite. +matchValidJSON :: FilePath -> SchemaSelector -> MatchBody +matchValidJSON schemaFile selector = + MatchBody $ \_headers body -> + case eitherDecode body of + Left err -> Just $ "failed to decode body: " <> err + Right value -> validateJSONPure value + where + -- NOTE: Uses unsafePerformIO to create a pure API although we are actually + -- calling an external program to verify the schema. This is fine, because the + -- call is referentially transparent and any given invocation of schema file, + -- selector and value will always yield the same result and can be shared. + validateJSONPure value = + unsafePerformIO $ do + validateJSON schemaFile selector value + pure Nothing diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/test/Hydra/JSONSchema.hs index ea5f24bc5f6..484a234fce1 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/test/Hydra/JSONSchema.hs @@ -8,7 +8,6 @@ import Hydra.Prelude import Test.Hydra.Prelude import Control.Arrow (left) -import Control.Exception (IOException) import Control.Lens (Traversal', at, (?~), (^..), (^?)) import Data.Aeson (Value, (.=)) import Data.Aeson qualified as Aeson @@ -23,17 +22,13 @@ import System.Directory (listDirectory) import System.Exit (ExitCode (..)) import System.FilePath (normalise, takeBaseName, takeExtension, (<.>), ()) import System.IO.Error (IOError, isDoesNotExistError) -import System.IO.Unsafe (unsafePerformIO) import System.Process (readProcessWithExitCode) import Test.QuickCheck (Property, counterexample, forAllShrink, resize, vectorOf) import Test.QuickCheck.Monadic (assert, monadicIO, monitor, run) import Prelude qualified --- | A schema validation error (like --- Data.OpenApi.Schema.Validation.ValidationError interface). -type ValidationError = String - --- | Validate a specific JSON value against a given JSON schema. +-- | Validate a specific JSON value against a given JSON schema and throws an +-- HUnitFailure exception if validation did not pass. -- -- The path to the schema must be a fully qualified path to .json schema file. -- Use 'withJsonSpecifications' to convert hydra-specific yaml schemas into @@ -53,55 +48,35 @@ type ValidationError = String -- which selects the JSON schema for "Address" types in a bigger specification, -- say an asyncapi description. validateJSON :: + HasCallStack => -- | Path to the JSON file holding the schema. FilePath -> -- | Selector into the JSON file pointing to the schema to be validated. - SpecificationSelector -> + SchemaSelector -> Value -> - Maybe ValidationError + IO () validateJSON schemaFilePath selector value = - -- NOTE: Use unsafePerformIO to create a pure API for testing API responses - -- around actually calling an external program to verify the schema. This is - -- fine, because the call is referentially transparent and any given - -- invocation of schema file, selector and value will always yield the same - -- result and can be shared. - unsafePerformIO - . handle anyIOExceptions - -- NOTE: We exit out of the do block deliberately using exceptions to retain - -- the temp directory for debugging (see 'withTempDir') - . handle convertFailure - . withTempDir "validateJSON" - $ \tmpDir -> do - ensureSystemRequirements - let jsonInput = tmpDir "jsonInput" - let jsonSchema = tmpDir "jsonSchema" - Aeson.eitherDecodeFileStrict schemaFilePath >>= \case - Left err -> fail $ "Failed to decode JSON schema " <> show schemaFilePath <> ": " <> err - Right schemaValue -> do - let jsonSpecSchema = - schemaValue ^? selector - <&> addField "$id" ("file://" <> tmpDir <> "/") - writeFileLBS jsonInput (Aeson.encode value) - writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) - (exitCode, out, err) <- - readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] "" - when (exitCode /= ExitSuccess) $ - failure $ - "exit code: " - <> show exitCode - <> "\n" - <> "stderr: " - <> err - <> "\n" - <> "stdout: " - <> out - pure Nothing - where - anyIOExceptions :: IOException -> IO (Maybe ValidationError) - anyIOExceptions e = pure . Just $ "IOException: " <> show e - - convertFailure :: SomeException -> IO (Maybe ValidationError) - convertFailure = pure . Just . displayException + withTempDir "validateJSON" $ \tmpDir -> do + ensureSystemRequirements + let jsonInput = tmpDir "jsonInput" + let jsonSchema = tmpDir "jsonSchema" + Aeson.eitherDecodeFileStrict schemaFilePath >>= \case + Left err -> fail $ "Failed to decode JSON schema " <> show schemaFilePath <> ": " <> err + Right schemaValue -> do + let jsonSpecSchema = + schemaValue ^? selector + <&> addField "$id" ("file://" <> tmpDir <> "/") + writeFileLBS jsonInput (Aeson.encode value) + writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) + (exitCode, out, err) <- + readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] "" + when (exitCode /= ExitSuccess) $ + failure . toString $ + unlines + [ "check-jsonschema failed on " <> toText jsonInput <> " with schema " <> toText jsonSchema + , toText out + , toText err + ] -- | Validate an 'Arbitrary' value against a JSON schema. -- @@ -112,7 +87,7 @@ prop_validateJSONSchema :: -- | Path to the JSON file holding the schema. FilePath -> -- | Selector into the JSON file pointing to the schema to be validated. - SpecificationSelector -> + SchemaSelector -> Property prop_validateJSONSchema specFileName selector = forAllShrink (resize 10 arbitrary) shrink $ \(samples :: [a]) -> @@ -173,9 +148,9 @@ prop_specIsComplete :: forall a. (Arbitrary a, Show a) => String -> - SpecificationSelector -> + SchemaSelector -> Property -prop_specIsComplete specFileName typeSpecificationSelector = +prop_specIsComplete specFileName selector = forAllShrink (vectorOf 1000 arbitrary) shrink $ \(a :: [a]) -> monadicIO $ do withJsonSpecifications $ \tmpDir -> do @@ -200,7 +175,7 @@ prop_specIsComplete specFileName typeSpecificationSelector = classify :: FilePath -> Maybe Aeson.Value -> [a] -> Map Text Integer classify _ (Just specs) = - let ks = specs ^.. typeSpecificationSelector . key "oneOf" . _Array . traverse . key "title" . _String + let ks = specs ^.. selector . key "oneOf" . _Array . traverse . key "title" . _String knownKeys = Map.fromList $ zip ks (repeat @Integer 0) @@ -213,7 +188,7 @@ prop_specIsComplete specFileName typeSpecificationSelector = -- | An alias for a traversal selecting some part of a 'Value' -- This alleviates the need for users of this module to import explicitly the types -- from aeson and lens. -type SpecificationSelector = Traversal' Aeson.Value Aeson.Value +type SchemaSelector = Traversal' Aeson.Value Aeson.Value -- | Prepare the environment (temp directory) with the JSON specifications. We -- maintain a YAML version of a JSON-schema, for it is more convenient to write. diff --git a/hydra-node/test/Hydra/JSONSchemaSpec.hs b/hydra-node/test/Hydra/JSONSchemaSpec.hs index b6538761af5..3c666508a88 100644 --- a/hydra-node/test/Hydra/JSONSchemaSpec.hs +++ b/hydra-node/test/Hydra/JSONSchemaSpec.hs @@ -4,11 +4,10 @@ module Hydra.JSONSchemaSpec where import Hydra.Prelude import Test.Hydra.Prelude +import Control.Exception (IOException) import Data.Aeson (Value (..), object, (.=)) import Data.Aeson.Lens (key) -import Data.Text (isInfixOf) import Hydra.JSONSchema (validateJSON, withJsonSpecifications) -import System.Environment (getEnv, setEnv) import System.FilePath (()) spec :: Spec @@ -17,20 +16,15 @@ spec = it "works using identity selector and Null input" $ withJsonSpecifications $ \dir -> validateJSON (dir "api.json") id Null - `shouldBe` Nothing it "fails on non-existing schema file" $ validateJSON ("does-not-exist.json") id Null - `shouldSatisfy` \case - Just err -> "does-not-exist.json" `isInfixOf` toText err - Nothing -> False + `shouldThrow` exceptionContaining @IOException "does-not-exist.json" it "fails with missing tool" $ do withClearedPATH $ validateJSON ("does-not-matter.json") id Null - `shouldSatisfy` \case - Just err -> "installed" `isInfixOf` toText err - Nothing -> False + `shouldThrow` exceptionContaining @IOException "installed" it "selects a sub-schema correctly" $ withJsonSpecifications $ \dir -> @@ -38,7 +32,6 @@ spec = (dir "api.json") (key "components" . key "schemas" . key "HeadId") (String "some-head-id") - `shouldBe` Nothing it "produces helpful errors" $ withJsonSpecifications $ \dir -> @@ -46,16 +39,5 @@ spec = (dir "api.json") (key "components" . key "schemas" . key "HeadId") (object ["foo" .= String "bar"]) - `shouldSatisfy` \case - Just err -> "{'foo': 'bar'} is not of type 'string'" `isInfixOf` toText err - Nothing -> False - --- | Clear PATH environment variable while executing given action. -withClearedPATH :: IO () -> IO () -withClearedPATH act = - bracket capture (setEnv "PATH") (const act) - where - capture = do - env <- getEnv "PATH" - setEnv "PATH" "" - pure env + `shouldThrow` exceptionContaining @HUnitFailure + "{'foo': 'bar'} is not of type 'string'" diff --git a/hydra-test-utils/src/Test/Hydra/Prelude.hs b/hydra-test-utils/src/Test/Hydra/Prelude.hs index 7d0a89bd9d9..7bd0fc85401 100644 --- a/hydra-test-utils/src/Test/Hydra/Prelude.hs +++ b/hydra-test-utils/src/Test/Hydra/Prelude.hs @@ -10,25 +10,27 @@ module Test.Hydra.Prelude ( genericCoverTable, forAll2, pickBlind, - - -- * HSpec re-exports module Test.Hspec, module Test.Hspec.QuickCheck, withTempDir, withLogFile, checkProcessHasNotDied, + exceptionContaining, + withClearedPATH, ) where import Hydra.Prelude import Test.Hspec import Test.Hspec.QuickCheck +import Data.List (isInfixOf) import Data.Ratio ((%)) import Data.Text.IO (hGetContents) import Data.Typeable (typeRep) import GHC.Exception (SrcLoc (..)) import GHC.IO.Exception (IOErrorType (..), IOException (..)) import System.Directory (createDirectoryIfMissing, removePathForcibly) +import System.Environment (getEnv, setEnv) import System.Exit (ExitCode (..)) import System.FilePath (takeDirectory) import System.IO.Temp (createTempDirectory, getCanonicalTemporaryDirectory) @@ -225,3 +227,23 @@ pickBlind gen = MkPropertyM $ \k -> do a <- gen mp <- k a pure (forAllBlind (return a) . const <$> mp) + +-- | Selector for use with 'shouldThrow' to select exceptions containing some +-- string. Use with TypeApplications, e.g. +-- +-- @@ +-- exceptionContaining @IOException "foo" +-- @@ +exceptionContaining :: Exception e => String -> Selector e +exceptionContaining msg e = + msg `isInfixOf` displayException e + +-- | Clear PATH environment variable while executing given action. +withClearedPATH :: IO () -> IO () +withClearedPATH act = + bracket capture (setEnv "PATH") (const act) + where + capture = do + env <- getEnv "PATH" + setEnv "PATH" "" + pure env From 04def7d0ded1539bdd7bd11ef843d1a300423fdb Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Mon, 8 Jan 2024 20:00:46 +0100 Subject: [PATCH 04/11] Remove unused vendored cardano.json schema --- hydra-node/json-schemas/cardanonical/LICENSE | 201 -- .../json-schemas/cardanonical/cardano.json | 1969 ----------------- 2 files changed, 2170 deletions(-) delete mode 100644 hydra-node/json-schemas/cardanonical/LICENSE delete mode 100644 hydra-node/json-schemas/cardanonical/cardano.json diff --git a/hydra-node/json-schemas/cardanonical/LICENSE b/hydra-node/json-schemas/cardanonical/LICENSE deleted file mode 100644 index 261eeb9e9f8..00000000000 --- a/hydra-node/json-schemas/cardanonical/LICENSE +++ /dev/null @@ -1,201 +0,0 @@ - Apache License - Version 2.0, January 2004 - http://www.apache.org/licenses/ - - TERMS AND CONDITIONS FOR USE, REPRODUCTION, AND DISTRIBUTION - - 1. Definitions. - - "License" shall mean the terms and conditions for use, reproduction, - and distribution as defined by Sections 1 through 9 of this document. - - "Licensor" shall mean the copyright owner or entity authorized by - the copyright owner that is granting the License. - - "Legal Entity" shall mean the union of the acting entity and all - other entities that control, are controlled by, or are under common - control with that entity. For the purposes of this definition, - "control" means (i) the power, direct or indirect, to cause the - direction or management of such entity, whether by contract or - otherwise, or (ii) ownership of fifty percent (50%) or more of the - outstanding shares, or (iii) beneficial ownership of such entity. - - "You" (or "Your") shall mean an individual or Legal Entity - exercising permissions granted by this License. - - "Source" form shall mean the preferred form for making modifications, - including but not limited to software source code, documentation - source, and configuration files. - - "Object" form shall mean any form resulting from mechanical - transformation or translation of a Source form, including but - not limited to compiled object code, generated documentation, - and conversions to other media types. - - "Work" shall mean the work of authorship, whether in Source or - Object form, made available under the License, as indicated by a - copyright notice that is included in or attached to the work - (an example is provided in the Appendix below). - - "Derivative Works" shall mean any work, whether in Source or Object - form, that is based on (or derived from) the Work and for which the - editorial revisions, annotations, elaborations, or other modifications - represent, as a whole, an original work of authorship. For the purposes - of this License, Derivative Works shall not include works that remain - separable from, or merely link (or bind by name) to the interfaces of, - the Work and Derivative Works thereof. - - "Contribution" shall mean any work of authorship, including - the original version of the Work and any modifications or additions - to that Work or Derivative Works thereof, that is intentionally - submitted to Licensor for inclusion in the Work by the copyright owner - or by an individual or Legal Entity authorized to submit on behalf of - the copyright owner. For the purposes of this definition, "submitted" - means any form of electronic, verbal, or written communication sent - to the Licensor or its representatives, including but not limited to - communication on electronic mailing lists, source code control systems, - and issue tracking systems that are managed by, or on behalf of, the - Licensor for the purpose of discussing and improving the Work, but - excluding communication that is conspicuously marked or otherwise - designated in writing by the copyright owner as "Not a Contribution." - - "Contributor" shall mean Licensor and any individual or Legal Entity - on behalf of whom a Contribution has been received by Licensor and - subsequently incorporated within the Work. - - 2. Grant of Copyright License. Subject to the terms and conditions of - this License, each Contributor hereby grants to You a perpetual, - worldwide, non-exclusive, no-charge, royalty-free, irrevocable - copyright license to reproduce, prepare Derivative Works of, - publicly display, publicly perform, sublicense, and distribute the - Work and such Derivative Works in Source or Object form. - - 3. Grant of Patent License. Subject to the terms and conditions of - this License, each Contributor hereby grants to You a perpetual, - worldwide, non-exclusive, no-charge, royalty-free, irrevocable - (except as stated in this section) patent license to make, have made, - use, offer to sell, sell, import, and otherwise transfer the Work, - where such license applies only to those patent claims licensable - by such Contributor that are necessarily infringed by their - Contribution(s) alone or by combination of their Contribution(s) - with the Work to which such Contribution(s) was submitted. If You - institute patent litigation against any entity (including a - cross-claim or counterclaim in a lawsuit) alleging that the Work - or a Contribution incorporated within the Work constitutes direct - or contributory patent infringement, then any patent licenses - granted to You under this License for that Work shall terminate - as of the date such litigation is filed. - - 4. Redistribution. You may reproduce and distribute copies of the - Work or Derivative Works thereof in any medium, with or without - modifications, and in Source or Object form, provided that You - meet the following conditions: - - (a) You must give any other recipients of the Work or - Derivative Works a copy of this License; and - - (b) You must cause any modified files to carry prominent notices - stating that You changed the files; and - - (c) You must retain, in the Source form of any Derivative Works - that You distribute, all copyright, patent, trademark, and - attribution notices from the Source form of the Work, - excluding those notices that do not pertain to any part of - the Derivative Works; and - - (d) If the Work includes a "NOTICE" text file as part of its - distribution, then any Derivative Works that You distribute must - include a readable copy of the attribution notices contained - within such NOTICE file, excluding those notices that do not - pertain to any part of the Derivative Works, in at least one - of the following places: within a NOTICE text file distributed - as part of the Derivative Works; within the Source form or - documentation, if provided along with the Derivative Works; or, - within a display generated by the Derivative Works, if and - wherever such third-party notices normally appear. The contents - of the NOTICE file are for informational purposes only and - do not modify the License. You may add Your own attribution - notices within Derivative Works that You distribute, alongside - or as an addendum to the NOTICE text from the Work, provided - that such additional attribution notices cannot be construed - as modifying the License. - - You may add Your own copyright statement to Your modifications and - may provide additional or different license terms and conditions - for use, reproduction, or distribution of Your modifications, or - for any such Derivative Works as a whole, provided Your use, - reproduction, and distribution of the Work otherwise complies with - the conditions stated in this License. - - 5. Submission of Contributions. Unless You explicitly state otherwise, - any Contribution intentionally submitted for inclusion in the Work - by You to the Licensor shall be under the terms and conditions of - this License, without any additional terms or conditions. - Notwithstanding the above, nothing herein shall supersede or modify - the terms of any separate license agreement you may have executed - with Licensor regarding such Contributions. - - 6. Trademarks. This License does not grant permission to use the trade - names, trademarks, service marks, or product names of the Licensor, - except as required for reasonable and customary use in describing the - origin of the Work and reproducing the content of the NOTICE file. - - 7. Disclaimer of Warranty. Unless required by applicable law or - agreed to in writing, Licensor provides the Work (and each - Contributor provides its Contributions) on an "AS IS" BASIS, - WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or - implied, including, without limitation, any warranties or conditions - of TITLE, NON-INFRINGEMENT, MERCHANTABILITY, or FITNESS FOR A - PARTICULAR PURPOSE. You are solely responsible for determining the - appropriateness of using or redistributing the Work and assume any - risks associated with Your exercise of permissions under this License. - - 8. Limitation of Liability. In no event and under no legal theory, - whether in tort (including negligence), contract, or otherwise, - unless required by applicable law (such as deliberate and grossly - negligent acts) or agreed to in writing, shall any Contributor be - liable to You for damages, including any direct, indirect, special, - incidental, or consequential damages of any character arising as a - result of this License or out of the use or inability to use the - Work (including but not limited to damages for loss of goodwill, - work stoppage, computer failure or malfunction, or any and all - other commercial damages or losses), even if such Contributor - has been advised of the possibility of such damages. - - 9. Accepting Warranty or Additional Liability. While redistributing - the Work or Derivative Works thereof, You may choose to offer, - and charge a fee for, acceptance of support, warranty, indemnity, - or other liability obligations and/or rights consistent with this - License. However, in accepting such obligations, You may act only - on Your own behalf and on Your sole responsibility, not on behalf - of any other Contributor, and only if You agree to indemnify, - defend, and hold each Contributor harmless for any liability - incurred by, or claims asserted against, such Contributor by reason - of your accepting any such warranty or additional liability. - - END OF TERMS AND CONDITIONS - - APPENDIX: How to apply the Apache License to your work. - - To apply the Apache License to your work, attach the following - boilerplate notice, with the fields enclosed by brackets "[]" - replaced with your own identifying information. (Don't include - the brackets!) The text should be enclosed in the appropriate - comment syntax for the file format. We also recommend that a - file or class name and description of purpose be included on the - same "printed page" as the copyright notice for easier - identification within third-party archives. - - Copyright [yyyy] [name of copyright owner] - - Licensed under the Apache License, Version 2.0 (the "License"); - you may not use this file except in compliance with the License. - You may obtain a copy of the License at - - http://www.apache.org/licenses/LICENSE-2.0 - - Unless required by applicable law or agreed to in writing, software - distributed under the License is distributed on an "AS IS" BASIS, - WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. - See the License for the specific language governing permissions and - limitations under the License. diff --git a/hydra-node/json-schemas/cardanonical/cardano.json b/hydra-node/json-schemas/cardanonical/cardano.json deleted file mode 100644 index fe64801ea59..00000000000 --- a/hydra-node/json-schemas/cardanonical/cardano.json +++ /dev/null @@ -1,1969 +0,0 @@ -{ "$schema": "https://json-schema.org/draft-07/schema" -, "$id": "cardano.json" -, "title": "Cardano" -, "definitions": - { "Address": - { "title": "Address" - , "type": "string" - , "description": "A Cardano address (either legacy format or new format)." - , "contentEncoding": "bech32|base58" - , "pattern": "[1-9A-HJ-NP-Za-km-z]*" - , "examples": - [ "addr1q9d34spgg2kdy47n82e7x9pdd6vql6d2engxmpj20jmhuc2047yqd4xnh7u6u5jp4t0q3fkxzckph4tgnzvamlu7k5psuahzcp" - , "DdzFFzCqrht8mbSTZHqpM2u4HeND2mdspsaBhdQ1BowPJBMzbDeBMeKgqdoKqo1D4sdPusEdZJVrFJRBBxX1jUEofNDYCJSZLg8MkyCE" - ] - } - - , "AddressAttributes": - { "title": "AddressAttributes" - , "type": "string" - , "description": "Extra attributes carried by Byron addresses (network magic and/or HD payload)." - , "contentEncoding": "base16" - } - - , "AssetQuantity": - { "title": "AssetQuantity" - , "type": "integer" - , "description": "A number of asset, can be negative went burning assets." - } - - , "Assets": - { "title": "Assets" - , "type": "object" - , "propertyNames": { "pattern": "^[0-9a-z]{56}$" } - , "additionalProperties": - { "type": "object" - , "propertyNames": { "pattern": "^[0-9a-z]{0,64}$" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/AssetQuantity" } - } - } - - , "Block": - { "title": "Block" - , "oneOf": - [ { "$ref": "cardano.json#/definitions/Block" } - , { "$ref": "cardano.json#/definitions/Block" } - , { "$ref": "cardano.json#/definitions/Block" } - ] - } - - , "Block": - { "title": "Block" - , "type": "object" - , "additionalProperties": false - , "required": - [ "id", "type", "era", "ancestor", "height" - ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "ebb" ] - } - , "era": - { "type": "string" - , "enum": [ "byron" ] - } - , "id": { "$ref": "cardano.json#/definitions/Digest" } - , "ancestor": { "$ref": "cardano.json#/definitions/Digest" } - , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } - } - } - - , "Block": - { "title": "Block" - , "type": "object" - , "additionalProperties": false - , "required": - [ "id", "era", "type", "ancestor", "height", "size", "slot" - , "protocol", "issuer", "delegate" - ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "bft" ] - } - , "era": - { "type": "string" - , "enum": [ "byron" ] - } - , "id": { "$ref": "cardano.json#/definitions/Digest" } - , "ancestor": { "$ref": "cardano.json#/definitions/Digest" } - , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } - , "slot": { "$ref": "cardano.json#/definitions/Slot" } - , "size": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "transactions": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Transaction" } - } - , "operationalCertificates": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/BootstrapOperationalCertificate"} - } - , "protocol": - { "type": "object" - , "additionalProperties": false - , "required": [ "id", "version", "software" ] - , "properties": - { "id": { "$ref": "cardano.json#/definitions/BootstrapProtocolId" } - , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } - , "software": { "$ref": "cardano.json#/definitions/SoftwareVersion" } - , "update": { "$ref": "cardano.json#/definitions/BootstrapProtocolUpdate" } - } - } - , "issuer": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/ExtendedVerificationKey" } - } - } - , "delegate": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/ExtendedVerificationKey" } - } - } - } - } - - , "Block": - { "title": "Block" - , "type": "object" - , "additionalProperties": false - , "required": - [ "id", "era", "type", "ancestor", "height", "size", "slot" - , "protocol", "issuer" - ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "praos" ] - } - , "era": - { "type": "string" - , "enum": [ "shelley", "allegra", "mary", "alonzo", "babbage" ] - } - , "id": { "$ref": "cardano.json#/definitions/Digest" } - , "ancestor": - { "oneOf": - [ { "$ref": "cardano.json#/definitions/Digest" } - , { "title": "GenesisHash", "type": "string", "enum": [ "genesis" ] } - ] - } - , "nonce": { "$ref": "cardano.json#/definitions/CertifiedVrf" } - , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } - , "size": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "slot": { "$ref": "cardano.json#/definitions/Slot" } - , "transactions": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Transaction" } - } - , "protocol": - { "type": "object" - , "additionalProperties": false - , "required": [ "version" ] - , "properties": - { "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } - } - } - , "issuer": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey", "vrfVerificationKey", "operationalCertificate", "leaderValue" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } - , "vrfVerificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } - , "operationalCertificate": { "$ref": "cardano.json#/definitions/OperationalCertificate" } - , "leaderValue": { "$ref": "cardano.json#/definitions/CertifiedVrf" } - } - } - } - } - - , "BlockHeight": - { "title": "BlockHeight" - , "type": "integer" - , "description": "A block number, the i-th block to be minted is number i." - , "minimum": 0 - , "maximum": 18446744073709552999 - } - - , "BootstrapProtocolUpdate": - { "title": "BootstrapProtocolUpdate" - , "type": "object" - , "additionalProperties": false - , "required": [ "votes" ] - , "properties": - { "proposal": - { "type": "object" - , "additionalProperties": false - , "required": [ "version", "software", "parameters", "metadata" ] - , "properties": - { "version": - { "$ref": "cardano.json#/definitions/ProtocolVersion" - } - , "software": - { "$ref": "cardano.json#/definitions/SoftwareVersion" - } - , "parameters": - { "$ref": "cardano.json#/definitions/BootstrapProtocolParameters" - } - , "metadata": - { "type": "object" - , "additionalProperties": { "type": "string" } - } - } - } - , "votes": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/BootstrapVote" } - } - } - } - - , "BootstrapOperationalCertificate": - { "title": "BootstrapOperationalCertificate" - , "type": "object" - , "description": "A (Byron) delegation certificate." - , "additionalProperties": false - , "required": [ "issuer", "delegate" ] - , "properties": - { "issuer": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } - } - } - , "delegate": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } - } - } - } - } - - , "BootstrapProtocolId": - { "title": "BootstrapProtocolId" - , "type": "integer" - , "minimum": 0 - , "maximum": 4294967295 - , "examples": - [ 764824073 - ] - } - - , "BootstrapProtocolParameters": - { "title": "BootstrapProtocolParameters" - , "type": "object" - , "additionalProperties": false - , "properties": - { "heavyDelegationThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxUpdateProposalSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "multiPartyComputationThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "scriptVersion": { "$ref": "cardano.json#/definitions/UInt64" } - , "slotDuration": { "$ref": "cardano.json#/definitions/UInt64" } - , "unlockStakeEpoch": { "$ref": "cardano.json#/definitions/UInt64" } - , "updateProposalThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "updateProposalTimeToLive": { "$ref": "cardano.json#/definitions/UInt64" } - , "updateVoteThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "softForkInitThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "softForkMinThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "softForkDecrementThreshold": { "$ref": "cardano.json#/definitions/Ratio" } - , "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } - } - } - - , "BootstrapVote": - { "title": "BootstrapVote" - , "type": "object" - , "additionalProperties": false - , "required": [ "voter", "proposal" ] - , "properties": - { "voter": - { "type": "object" - , "additionalProperties": false - , "required": [ "verificationKey" ] - , "properties": - { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } - } - } - , "proposal": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": { "$ref": "cardano.json#/definitions/Digest" } - } - } - } - } - - , "Bound": - { "title": "Bound" - , "type": "object" - , "description": "An era bound which captures the time, slot and epoch at which the era start. The time is relative to the start time of the network." - , "additionalProperties": false - , "required": ["time", "slot", "epoch"] - , "properties": - { "time": { "$ref": "cardano.json#/definitions/RelativeTime" } - , "slot": { "$ref": "cardano.json#/definitions/Slot" } - , "epoch": { "$ref": "cardano.json#/definitions/Epoch" } - } - } - - , "Certificate": - { "title": "Certificate" - , "oneOf": - [ { "type": "object" - , "description": "A stake delegation certificate, from a delegator to a stake pool." - , "title": "stakeDelegation" - , "additionalProperties": false - , "required": [ "type", "credential", "stakePool" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "stakeDelegation" ] - } - , "credential": - { "$ref": "cardano.json#/definitions/Digest" - } - , "stakePool": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/StakePoolId" - } - } - } - } - } - , { "type": "object" - , "description": "A stake credential (key or script) registration certificate." - , "title": "stakeCredentialRegistration" - , "additionalProperties": false - , "required": [ "type", "credential" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "stakeCredentialRegistration" ] - } - , "credential": - { "$ref": "cardano.json#/definitions/Digest" - } - } - } - , { "type": "object" - , "description": "A stake key de-registration certificate." - , "title": "stakeCredentialDeregistration" - , "additionalProperties": false - , "required": [ "type", "credential" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "stakeCredentialDeregistration" ] - } - , "credential": - { "$ref": "cardano.json#/definitions/Digest" - } - } - } - , { "type": "object" - , "description": "A stake pool registration certificate." - , "title": "stakePoolRegistration" - , "additionalProperties": false - , "required": [ "type", "stakePool" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "stakePoolRegistration" ] - } - , "stakePool": - { "$ref": "cardano.json#/definitions/StakePool" - } - } - } - , { "type": "object" - , "description": "A stake pool retirement certificate." - , "additionalProperties": false - , "title": "stakePoolRetirement" - , "required": [ "type", "stakePool"] - , "properties": - { "type": - { "type": "string" - , "enum": [ "stakePoolRetirement" ] - } - , "stakePool": - { "type": "object" - , "additionalProperties": false - , "required": [ "id", "retirementEpoch" ] - , "properties": - { "retirementEpoch": { "$ref": "cardano.json#/definitions/Epoch" } - , "id": { "$ref": "cardano.json#/definitions/StakePoolId" } - } - } - } - } - , { "type": "object" - , "title": "genesisDelegation" - , "additionalProperties": false - , "required": [ "type", "delegate", "issuer" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "genesisDelegation" ] - } - , "delegate": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/Digest" - } - } - } - , "issuer": - { "type": "object" - , "additionalProperties": false - , "required": [ "id", "vrfVerificationKeyHash" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/Digest" - } - , "vrfVerificationKeyHash": - { "$ref": "cardano.json#/definitions/Digest" - } - } - } - } - } - , { "title": "TreasuryTransfer" - , "oneOf": - [ { "type": "object" - , "title": "TreasuryTransfer" - , "description": "A transfer from or to the treasury / reserves authored by genesis delegates." - , "additionalProperties": false - , "required": [ "type", "source", "target", "value" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "treasuryTransfer" ] - } - , "source": - { "type": "string" - , "enum": [ "reserves", "treasury" ] - } - , "target": - { "type": "string" - , "enum": [ "reserves", "treasury" ] - } - , "value": - { "$ref": "cardano.json#/definitions/Lovelace" - } - } - } - , { "type": "object" - , "title": "TreasuryTransfer" - , "description": "A transfer from or to the treasury / reserves authored by genesis delegates." - , "additionalProperties": false - , "required": [ "type", "source", "target", "rewards" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "treasuryTransfer" ] - } - , "source": - { "type": "string" - , "enum": [ "reserves", "treasury" ] - } - , "target": - { "type": "string" - , "enum": [ "rewardAccounts" ] - } - , "rewards": - { "$ref": "cardano.json#/definitions/RewardTransfer" - } - } - } - ] - } - ] - } - - , "CertifiedVrf": - { "title": "CertifiedVrf" - , "type": "object" - , "additionalProperties": false - , "properties": - { "proof": { "$ref": "cardano.json#/definitions/VrfProof" } - , "output": { "$ref": "cardano.json#/definitions/VrfOutput" } - } - } - - , "ChainCode": - { "title": "ChainCode" - , "type": "string" - , "description": "An Ed25519-BIP32 chain-code for key deriviation." - , "contentEncoding": "base16" - } - - , "CostModels": - { "title": "CostModels" - , "type": "object" - , "additionalProperties": { "$ref": "cardano.json#/definitions/CostModel" } - , "propertyNames": { "$ref": "cardano.json#/definitions/Language" } - , "examples": - [ { "plutus:v1": - { "k": 14 - , "a": 123 - } - } - ] - } - - , "CostModel": - { "title": "CostModel" - , "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Int64" } - } - - , "Datum": - { "title": "Datum" - , "type": "string" - , "contentEncoding": "base16" - } - - , "Digest": - { "title": "Digest" - , "type": "string" - , "description": "A hash digest from an unspecified algorithm and length." - , "contentEncoding": "base16" - , "examples": - [ "90181c517a5beadc9c3fe64bf8" - ] - } - - , "Digest": - { "title": "Digest" - , "type": "string" - , "description": "A Blake2b 28-byte hash digest, encoded in base16." - , "contentEncoding": "base16" - , "minLength": 56 - , "maxLength": 56 - , "examples": - [ "90181c517a5beadc9c3fe64bf821d3e889a963fc717003ec248757d3" - ] - } - - , "Digest": - { "title": "Digest" - , "type": "string" - , "description": "A Blake2b 32-byte hash digest, encoded in base16." - , "contentEncoding": "base16" - , "minLength": 64 - , "maxLength": 64 - , "examples": - [ "c248757d390181c517a5beadc9c3fe64bf821d3e889a963fc717003ec248757d" - ] - } - - , "Epoch": - { "title": "Epoch" - , "type": "integer" - , "description": "An epoch number or length." - , "minimum": 0 - , "maximum": 18446744073709552000 - } - - , "Era": - { "title": "Era" - , "type": "string" - , "enum": [ "byron", "shelley", "allegra", "mary", "alonzo", "babbage", "conway" ] - } - - , "EraWithGenesis": - { "title": "EraWithGenesis" - , "type": "string" - , "enum": [ "byron", "shelley", "alonzo", "conway" ] - } - - , "EraParameters": - { "title": "EraParameters" - , "type": "object" - , "description": "Parameters that can vary across hard forks." - , "additionalProperties": false - , "required": [ "epochLength", "slotLength", "safeZone" ] - , "properties": - { "epochLength": { "$ref": "cardano.json#/definitions/Epoch" } - , "slotLength": { "$ref": "cardano.json#/definitions/SlotLength" } - , "safeZone": - { "oneOf": - [ { "$ref": "cardano.json#/definitions/SafeZone" } - , { "type": "null" } - ] - } - } - } - - , "EraSummary": - { "title": "EraSummary" - , "type": "object" - , "description": "Summary of the confirmed parts of the ledger." - , "additionalProperties": false - , "required": [ "start", "parameters" ] - , "properties": - { "start": { "$ref": "cardano.json#/definitions/Bound" } - , "end": { "$ref": "cardano.json#/definitions/Bound" } - , "parameters": { "$ref": "cardano.json#/definitions/EraParameters" } - } - } - - , "ExecutionUnits": - { "title": "ExecutionUnits" - , "type": "object" - , "additionalProperties": false - , "required": [ "memory", "cpu" ] - , "properties": - { "memory": { "$ref": "cardano.json#/definitions/UInt64" } - , "cpu": { "$ref": "cardano.json#/definitions/UInt64" } - } - } - - , "Genesis": - { "title": "Genesis" - , "type": "object" - , "description": "A Byron genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." - , "additionalProperties": false - , "required": - [ "era" - , "genesisKeyHashes" - , "genesisDelegations" - , "startTime" - , "initialFunds" - , "initialVouchers" - , "securityParameter" - , "networkMagic" - , "protocolParameters" - ] - , "properties": - { "era": - { "type": "string" - , "enum": [ "byron" ] - } - , "genesisKeyHashes": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Digest" } - } - , "genesisDelegations": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/Digest" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/BootstrapOperationalCertificate" } - } - , "startTime": { "$ref": "cardano.json#/definitions/UtcTime" } - , "initialFunds": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/Address" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } - } - , "initialVouchers": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/VerificationKey" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } - } - , "securityParameter": { "$ref": "cardano.json#/definitions/UInt64" } - , "networkMagic": { "$ref": "cardano.json#/definitions/NetworkMagic" } - , "protocolParameters": { "$ref": "cardano.json#/definitions/ProtocolParameters" } - } - } - - , "Genesis": - { "title": "Genesis" - , "type": "object" - , "description": "A Shelley genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." - , "additionalProperties": false - , "required": - [ "era" - , "startTime" - , "networkMagic" - , "network" - , "activeSlotsCoefficient" - , "securityParameter" - , "epochLength" - , "slotsPerKesPeriod" - , "maxKesEvolutions" - , "slotLength" - , "updateQuorum" - , "maxLovelaceSupply" - , "initialParameters" - , "initialDelegates" - , "initialFunds" - , "initialStakePools" - ] - , "properties": - { "era": - { "type": "string" - , "enum": [ "shelley" ] - } - , "startTime": { "$ref": "cardano.json#/definitions/UtcTime" } - , "networkMagic": { "$ref": "cardano.json#/definitions/NetworkMagic" } - , "network": { "$ref": "cardano.json#/definitions/Network" } - , "activeSlotsCoefficient": { "$ref": "cardano.json#/definitions/Ratio" } - , "securityParameter": { "$ref": "cardano.json#/definitions/UInt64" } - , "epochLength": { "$ref": "cardano.json#/definitions/Epoch" } - , "slotsPerKesPeriod": { "$ref": "cardano.json#/definitions/UInt64" } - , "maxKesEvolutions": { "$ref": "cardano.json#/definitions/UInt64" } - , "slotLength": { "$ref": "cardano.json#/definitions/SlotLength" } - , "updateQuorum": { "$ref": "cardano.json#/definitions/UInt64" } - , "maxLovelaceSupply": { "$ref": "cardano.json#/definitions/UInt64" } - , "initialParameters": { "$ref": "cardano.json#/definitions/ProtocolParameters" } - , "initialDelegates": { "$ref": "cardano.json#/definitions/InitialDelegates" } - , "initialFunds": - { "type": "object" - , "title": "InitialFunds" - , "propertyNames": { "$ref": "cardano.json#/definitions/Address" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } - } - , "initialStakePools": { "$ref": "cardano.json#/definitions/GenesisStakePools" } - } - } - - , "Genesis": - { "title": "Genesis" - , "type": "object" - , "description": "An Alonzo genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." - , "additionalProperties": false - , "required": - [ "era" - , "initialParameters" - ] - , "properties": - { "era": - { "type": "string" - , "enum": [ "alonzo" ] - } - , "initialParameters": - { "type": "object" - , "additionalProperties": false - , "required": - [ "minUtxoDepositCoefficient" - , "collateralPercentage" - , "plutusCostModels" - , "maxCollateralInputs" - , "maxExecutionUnitsPerBlock" - , "maxExecutionUnitsPerTransaction" - , "maxValueSize" - , "scriptExecutionPrices" - ] - , "properties": - { "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } - , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } - , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } - , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } - } - } - } - } - - , "Genesis": - { "title": "Genesis" - , "type": "object" - , "description": "An Conway genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." - , "additionalProperties": false - , "required": - [ "era" - , "initialDelegates" - ] - , "properties": - { "era": - { "type": "string" - , "enum": [ "conway" ] - } - , "initialDelegates": - { "$ref": "cardano.json#/definitions/InitialDelegates" - } - } - } - - , "GenesisDelegate": - { "title": "GenesisDelegate" - , "type": "object" - , "description": "A Genesis delegate, in charge of Cardano's governance." - , "additionalProperties": false - , "required": - [ "vrfVerificationKeyHash" - , "id" - ] - , "properties": - { "id": { "$ref": "cardano.json#/definitions/Digest" } - , "vrfVerificationKeyHash": { "$ref": "cardano.json#/definitions/Digest" } - } - } - - , "GenesisStakePools": - { "title": "GenesisStakePools" - , "type": "object" - , "description": "A Genesis stake pools configuration; primarily used for bootstrapping test networks." - , "additionalProperties": false - , "required": - [ "stakePools" - , "delegators" - ] - , "properties": - { "stakePools": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/StakePoolId" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/StakePool" } - } - , "delegators": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/Digest" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/StakePoolId" } - } - } - } - - , "GovernanceAction": - { "oneOf": - [ { "title": "GovernanceAction" - , "type": "object" - , "additionalProperties": false - , "required": [ "type", "parameters" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "protocolParametersUpdate" ] - } - , "parameters": - { "$ref": "cardano.json#/definitions/ProposedProtocolParameters" - } - } - } - ] - } - - , "GovernanceActionReference": - { "title": "GovernanceActionReference" - , "type": "object" - , "additionalProperties": false - , "required": [ "transaction", "governanceAction" ] - , "properties": - { "transaction": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/TransactionId" - } - } - } - , "governanceAction": - { "$ref": "cardano.json#/definitions/Index" - } - } - } - - , "ExtendedVerificationKey": - { "title": "ExtendedVerificationKey" - , "type": "string" - , "description": "An Ed25519-BIP32 Byron genesis delegate verification key with chain-code." - , "contentEncoding": "base16" - , "minLength": 128 - , "maxLength": 128 - } - - , "Index": - { "type": "object" - , "additionalProperties": false - , "required": [ "index" ] - , "properties": - { "index": - { "$ref": "cardano.json#/definitions/UInt32" - } - } - } - - , "InitialDelegates": - { "title": "InitialDelegates" - , "type": "array" - , "items": - { "type": "object" - , "additionalProperties": false - , "required": [ "issuer", "delegate" ] - , "properties": - { "issuer": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": { "$ref": "cardano.json#/definitions/Digest" } - } - } - , "delegate": - { "$ref": "cardano.json#/definitions/GenesisDelegate" - } - } - } - } - - , "Int64": - { "title": "Int64" - , "type": "integer" - , "minimum": -9223372036854775808 - , "maximum": 9223372036854775807 - } - - , "InputSource": - { "type": "string" - , "enum": - [ "inputs" - , "collaterals" - ] - } - - , "Language": - { "title": "Language" - , "type": "string" - , "enum": [ "plutus:v1", "plutus:v2", "plutus:v3" ] - } - - , "Lovelace": - { "title": "Lovelace" - , "additionalProperties": false - , "required": [ "lovelace" ] - , "properties": - { "lovelace": - { "type": "integer" - , "description": "A number of lovelace, possibly large when summed up." - } - } - } - - , "LovelaceDelta": - { "title": "LovelaceDelta" - , "type": "object" - , "additionalProperties": false - , "required": [ "lovelace" ] - , "properties": - { "lovelace": - { "type": "integer" - , "description": "An amount, possibly negative, in Lovelace (1e6 Lovelace = 1 Ada)." - , "minimum": -9223372036854775808 - , "maximum": 9223372036854775807 - } - } - } - - , "KesVerificationKey": - { "title": "KesVerificationKey" - , "type": "string" - , "contentEncoding": "base16" - } - - , "Metadata": - { "title": "Metadata" - , "type": "object" - , "additionalProperties": false - , "required": [ "hash", "labels" ] - , "properties": - { "hash": { "$ref": "cardano.json#/definitions/Digest" } - , "labels": { "$ref": "cardano.json#/definitions/MetadataLabels" } - } - } - - , "MetadataLabels": - { "title": "MetadataLabels" - , "type": "object" - , "propertyNames": { "pattern": "^-?[0-9]+$" } - , "additionalProperties": - { "type": "object" - , "description": "An associated metadatum, as a CBOR bytestring or a JSON object if possible. Some binary representations cannot be represented in plain JSON and the 'json' field is therefore omitted." - , "required": [ "cbor" ] - , "additionalProperties": false - , "properties": - { "cbor": - { "type": "string" - , "contentEncoding": "base16" - , "pattern": "^[0-9a-f]*$" - } - , "json": - { "$ref": "cardano.json#/definitions/Metadatum" - } - } - } - } - - , "Metadatum": - { "title": "Metadatum" - , "oneOf": - [ { "title": "Integer", "type": "integer" } - , { "title": "String", "type": "string" } - , { "title": "Array", "type": "array", "items": { "$ref": "cardano.json#/definitions/Metadatum" } } - , { "title": "Object", "type": "object", "additionalProperties": { "$ref": "cardano.json#/definitions/Metadatum" } } - ] - } - - , "Network": - { "title": "Network" - , "type": "string" - , "description": "A network target, as defined since the Shelley era." - , "enum": [ "mainnet", "testnet" ] - } - - , "NetworkMagic": - { "title": "NetworkMagic" - , "type": "integer" - , "description": "A magic number for telling networks apart. (e.g. 764824073)" - , "minimum": 0 - , "maximum": 4294967296 - , "examples": - [ 764824073 - ] - } - - , "Nonce": - { "title": "Nonce" - , "oneOf": - [ { "type": "string" - , "enum": ["neutral"] - , "title": "neutral" - } - , { "$ref": "cardano.json#/definitions/Digest" } - ] - } - - , "Null": - { "type": "null" - } - - , "NumberOfBytes": - { "type": "object" - , "additionalProperties": false - , "required": [ "bytes" ] - , "properties": - { "bytes": { "$ref": "cardano.json#/definitions/Int64" } - } - } - - , "OperationalCertificate": - { "title": "OperationalCertificate" - , "type": "object" - , "description": "Certificate identifying a stake pool operator." - , "additionalProperties": false - , "required": [ "count", "kes" ] - , "properties": - { "count": { "$ref": "cardano.json#/definitions/UInt64" } - , "kes": - { "type": "object" - , "additionalProperties": false - , "required": [ "period", "verificationKey" ] - , "properties": - { "period": { "$ref": "cardano.json#/definitions/UInt64" } - , "verificationKey": { "$ref": "cardano.json#/definitions/KesVerificationKey" } - } - } - } - } - - , "Origin": - { "title": "Origin" - , "type": "string" - , "description": "The origin of the blockchain. This point is special in the sense that it doesn't point to any existing slots, but is preceding any existing other point." - , "enum": [ "origin" ] - } - - , "PolicyId": - { "title": "PolicyId" - , "$ref": "cardano.json#/definitions/Digest" - } - - , "StakePool": - { "title": "StakePool" - , "type": "object" - , "additionalProperties": false - , "required": - [ "id" - , "cost" - , "margin" - , "owners" - , "pledge" - , "relays" - , "rewardAccount" - , "vrfVerificationKeyHash" - ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/StakePoolId" - } - , "vrfVerificationKeyHash": - { "$ref": "cardano.json#/definitions/Digest" - } - , "owners": - { "type": "array" - , "items": - { "$ref": "cardano.json#/definitions/Digest" - } - } - , "cost": - { "$ref": "cardano.json#/definitions/Lovelace" - } - , "margin": - { "$ref": "cardano.json#/definitions/Ratio" - } - , "pledge": - { "$ref": "cardano.json#/definitions/Lovelace" - } - , "rewardAccount": - { "$ref": "cardano.json#/definitions/RewardAccount" - } - , "metadata": - { "type": "object" - , "title": "poolMetadata" - , "additionalProperties": false - , "required": ["hash","url"] - , "properties": - { "hash": { "$ref": "cardano.json#/definitions/Digest" } - , "url": - { "type": "string" - , "format": "uri" - } - } - } - , "relays": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Relay" } - } - } - } - - , "StakePoolId": - { "title": "StakePoolId" - , "type": "string" - , "description": "A Blake2b 32-byte hash digest of a pool's verification key." - , "contentEncoding": "bech32" - , "pattern": "^pool1[0-9a-z]*$" - , "examples": - [ "pool1qqqqpanw9zc0rzh0yp247nzf2s35uvnsm7aaesfl2nnejaev0uc" - , "pool1qqqqqdk4zhsjuxxd8jyvwncf5eucfskz0xjjj64fdmlgj735lr9" - ] - } - - , "ProposedProtocolParameters": - { "title": "ProposedProtocolParameters" - , "type": "object" - , "additionalProperties": false - , "properties": - { "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } - , "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "minUtxoDepositConstant": { "$ref": "cardano.json#/definitions/Lovelace" } - , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "extraEntropy": { "$ref": "cardano.json#/definitions/Nonce" } - , "stakeCredentialDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } - , "stakePoolDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } - , "stakePoolRetirementEpochBound": { "$ref": "cardano.json#/definitions/UInt64" } - , "stakePoolPledgeInfluence": { "$ref": "cardano.json#/definitions/Ratio" } - , "minStakePoolCost": { "$ref": "cardano.json#/definitions/Lovelace" } - , "desiredNumberOfStakePools": { "$ref": "cardano.json#/definitions/UInt64" } - , "federatedBlockProductionRatio": { "$ref": "cardano.json#/definitions/Ratio" } - , "monetaryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } - , "treasuryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } - , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } - , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } - , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } - , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } - , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } - } - } - - , "ProtocolParameters": - { "title": "ProtocolParameters" - , "type": "object" - , "additionalProperties": false - , "required": - [ "minFeeCoefficient" - , "minFeeConstant" - , "minUtxoDepositCoefficient" - , "minUtxoDepositConstant" - , "maxBlockBodySize" - , "maxBlockHeaderSize" - , "stakeCredentialDeposit" - , "stakePoolDeposit" - , "stakePoolRetirementEpochBound" - , "stakePoolPledgeInfluence" - , "minStakePoolCost" - , "monetaryExpansion" - , "treasuryExpansion" - , "desiredNumberOfStakePools" - , "version" - ] - , "properties": - { "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } - , "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } - , "minUtxoDepositConstant": { "$ref": "cardano.json#/definitions/Lovelace" } - , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } - , "extraEntropy": { "$ref": "cardano.json#/definitions/Nonce" } - , "stakeCredentialDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } - , "stakePoolDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } - , "stakePoolRetirementEpochBound": { "$ref": "cardano.json#/definitions/UInt64" } - , "stakePoolPledgeInfluence": { "$ref": "cardano.json#/definitions/Ratio" } - , "minStakePoolCost": { "$ref": "cardano.json#/definitions/Lovelace" } - , "desiredNumberOfStakePools": { "$ref": "cardano.json#/definitions/UInt64" } - , "federatedBlockProductionRatio": { "$ref": "cardano.json#/definitions/Ratio" } - , "monetaryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } - , "treasuryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } - , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } - , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } - , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } - , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } - , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } - } - } - - , "ProtocolVersion": - { "title": "ProtocolVersion" - , "type": "object" - , "additionalProperties": false - , "required": [ "major", "minor" ] - , "properties": - { "major": { "$ref": "cardano.json#/definitions/UInt32" } - , "minor": { "$ref": "cardano.json#/definitions/UInt32" } - , "patch": { "$ref": "cardano.json#/definitions/UInt32" } - } - } - - , "Ratio": - { "title": "Ratio" - , "type": "string" - , "description": "A ratio of two integers, to express exact fractions." - , "pattern": "^-?[0-9]+/[0-9]+$" - , "examples": - [ "2/3" - , "7/8" - ] - } - - , "Redeemer": - { "title": "Redeemer" - , "type": "object" - , "examples": - [ { "executionUnits": - { "memory": 2 - , "cpu": 2 - } - , "redeemer": "ggRCqSQ=" - } - ] - , "additionalProperties": false - , "required": [ "redeemer", "executionUnits" ] - , "properties": - { "redeemer": { "$ref": "cardano.json#/definitions/RedeemerData" } - , "executionUnits": { "$ref": "cardano.json#/definitions/ExecutionUnits" } - } - } - - , "RedeemerData": - { "title": "RedeemerData" - , "type": "string" - , "contentEncoding": "base16" - , "description": "Plutus data, CBOR-serialised." - } - - , "RedeemerPointer": - { "title": "RedeemerPointer" - , "type": "string" - , "pattern": "^(spend|mint|certificate|withdrawal):[0-9]+$" - } - - , "RelativeTime": - { "title": "RelativeTime" - , "type": "number" - , "description": "A time in seconds relative to another one (typically, system start or era start)." - } - - , "Relay": - { "title": "Relay" - , "oneOf": - [ { "type": "object" - , "title": "by address" - , "additionalProperties": false - , "required": [ "type" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "ipAddress" ] - } - , "ipv4": - { "type": "string" - } - , "ipv6": - { "type": "string" - } - , "port": - { "type": "integer" - , "minimum": 0 - , "maximum": 65535 - } - } - } - , { "type": "object" - , "title": "by name" - , "additionalProperties": false - , "required": [ "type", "hostname" ] - , "properties": - { "type": - { "type": "string" - , "enum": [ "hostname" ] - } - , "hostname": - { "type": "string" - } - , "port": - { "type": "integer" - , "minimum": 0 - , "maximum": 65535 - } - } - } - ] - } - - , "RewardAccount": - { "title": "RewardAccount" - , "type": "string" - , "description": "A reward account, also known as 'stake address'." - , "contentEncoding": "bech32" - , "pattern": "^stake(_test)?1[0-9a-z]+$" - , "examples": - [ "stake1ux7pt9adw8z46tgqn2f8fvurrhk325gcm4mf75mkmmxpx6gae9mzv" - ] - } - - , "RewardTransfer": - { "title": "RewardTransfer" - , "type": "object" - , "additionalProperties": { "$ref": "cardano.json#/definitions/LovelaceDelta" } - , "propertyNames": { "pattern": "[0-9a-f]{56}$" } - , "examples": - [ { "6d06fe0a5a8cb6d2bcc352581dea626bb5b2f66edf85678b2f2fa7b5": 123456789 - } - ] - } - - , "SafeZone": - { "title": "SafeZone" - , "type": "integer" - , "description": "Number of slots from the tip of the ledger in which it is guaranteed that no hard fork can take place. This should be (at least) the number of slots in which we are guaranteed to have k blocks." - , "minimum": 0 - , "maximum": 18446744073709552999 - } - - , "Script": - { "title": "Script" - , "oneOf": - [ { "type": "object" - , "title": "Native" - , "additionalProperties": false - , "required": [ "language", "cbor", "json" ] - , "properties": - { "language": - { "type": "string" - , "enum": [ "native" ] - } - , "json": - { "$ref": "cardano.json#/definitions/Script" - } - , "cbor": - { "type": "string" - , "contentEncoding": "base16" - } - } - } - , { "type": "object" - , "title": "Plutus" - , "additionalProperties": false - , "required": [ "language", "cbor" ] - , "properties": - { "language": - { "type": "string" - , "enum": [ "plutus:v1", "plutus:v2", "plutus:v3" ] - } - , "cbor": - { "type": "string" - , "contentEncoding": "base16" - } - } - } - ] - } - - , "Script": - { "title": "Script" - , "description": "A phase-1 monetary script. Timelocks constraints are only supported since Allegra." - , "examples": - [ { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } - , { "clause": "all" - , "from": - [ { "clause": "signature", "from": "ec09e5293d384637cd2f004356ef320f3fe3c07030e36bfffe67e2e2" } - , { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } - ] - } - , { "clause": "some" - , "atLeast": 2 - , "from": - [ { "clause": "signature", "from": "ec09e5293d384637cd2f004356ef320f3fe3c07030e36bfffe67e2e2" } - , { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } - , { "clause": "after", "slot": 42 } - ] - } - ] - , "oneOf": - [ { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "from" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "signature" ] - } - , "from": - { "$ref": "cardano.json#/definitions/Digest" - } - } - } - , { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "from" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "any" ] - } - , "from": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Script" } - } - } - } - - , { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "from" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "all" ] - } - , "from": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Script" } - } - } - } - , { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "from", "atLeast" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "some" ] - } - , "atLeast": - { "type": "integer" - } - , "from": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Script" } - } - } - } - , { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "slot" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "before" ] - } - , "slot": - { "$ref": "cardano.json#/definitions/Slot" - } - } - } - , { "type": "object" - , "title": "Clause" - , "additionalProperties": false - , "required": [ "clause", "slot" ] - , "properties": - { "clause": - { "type": "string" - , "enum": [ "after" ] - } - , "slot": - { "$ref": "cardano.json#/definitions/Slot" - } - } - } - ] - } - - , "ScriptExecutionPrices": - { "title": "ScriptExecutionPrices" - , "type": "object" - , "additionalProperties": false - , "required": [ "memory", "cpu" ] - , "properties": - { "memory": { "$ref": "cardano.json#/definitions/Ratio" } - , "cpu": { "$ref": "cardano.json#/definitions/Ratio" } - } - } - - , "ScriptPurpose": - { "title": "ScriptPurpose" - , "oneOf": - [ { "title": "spend" - , "type": "object" - , "additionalProperties": false - , "required": [ "purpose", "outputReference" ] - , "properties": - { "purpose": - { "type": "string" - , "enum": [ "spend" ] - } - , "outputReference": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } - } - } - , { "title": "mint" - , "type": "object" - , "additionalProperties": false - , "required": [ "purpose", "policy" ] - , "properties": - { "purpose": - { "type": "string" - , "enum": [ "mint" ] - } - , "policy": { "$ref": "cardano.json#/definitions/PolicyId" } - } - } - , { "title": "publish" - , "type": "object" - , "additionalProperties": false - , "required": [ "purpose", "certificate" ] - , "properties": - { "purpose": - { "type": "string" - , "enum": [ "publish" ] - } - , "certificate": { "$ref": "cardano.json#/definitions/Certificate" } - } - } - , { "title": "withdraw" - , "type": "object" - , "additionalProperties": false - , "required": [ "purpose", "rewardAccount" ] - , "properties": - { "purpose": - { "type": "string" - , "enum": [ "withdraw" ] - } - , "rewardAccount": { "$ref": "cardano.json#/definitions/RewardAccount" } - } - } - ] - } - - , "Signature": - { "title": "Signature" - , "type": "string" - , "description": "An EdDSA signature." - , "contentEncoding": "base16" - , "minLength": 128 - , "maxLength": 128 - } - - , "Signatory": - { "title": "Signatory" - , "type": "object" - , "additionalProperties": false - , "required": [ "signature", "key" ] - , "properties": - { "key": { "$ref": "cardano.json#/definitions/VerificationKey" } - , "signature": { "$ref": "cardano.json#/definitions/Signature" } - , "chainCode": { "$ref": "cardano.json#/definitions/ChainCode" } - , "addressAttributes": { "$ref": "cardano.json#/definitions/AddressAttributes" } - } - , "examples": - [ { "signature": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b4ffffffff" - , "key": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01" - , "addressAttributes": "cA==" - , "chainCode": "b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b450" - } - , { "signature": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b4ffffffff" - , "key": "0c02af01eaacc939b3d0d817f4eb57d323ea5686cb1fecb8de821df1296b84a7" - } - ] - } - - , "Slot": - { "title": "Slot" - , "description": "An absolute slot number." - , "type": "integer" - , "minimum": 0 - , "maximum": 18446744073709552000 - } - - , "SlotLength": - { "title": "SlotLength" - , "description": "A slot length, in seconds, possibly with decimals." - , "type": "object" - , "additionalProperties": false - , "required": [ "seconds" ] - , "properties": - { "seconds": - { "type": "number" - } - } - } - - , "SoftwareVersion": - { "title": "SoftwareVersion" - , "type": "object" - , "additionalProperties": false - , "required": [ "appName", "number" ] - , "properties": - { "appName": { "type": "string" } - , "number": { "$ref": "cardano.json#/definitions/UInt32" } - } - } - - , "StakeAddress": - { "title": "StakeAddress" - , "type": "string" - , "description": "A stake address (a.k.a reward account)" - , "contentEncoding": "bech32" - , "pattern": "^(stake|stake_test)1[0-9a-z]*$" - , "examples": - [ "stake179kzq4qulejydh045yzxwk4ksx780khkl4gdve9kzwd9vjcek9u8h" - ] - } - - , "Tip": - { "title": "tip" - , "type": "object" - , "additionalProperties": false - , "required": [ "slot", "id", "blockNo" ] - , "properties": - { "slot": { "$ref": "cardano.json#/definitions/Slot" } - , "id": { "$ref": "cardano.json#/definitions/Digest" } - , "blockNo": { "$ref": "cardano.json#/definitions/BlockHeight" } - } - } - - , "Transaction": - { "title": "Transaction" - , "type": "object" - , "additionalProperties": false - , "required": [ "id", "inputSource", "inputs", "outputs", "signatories", "cbor" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/Digest" - } - , "inputSource": - { "$ref": "cardano.json#/definitions/InputSource" - } - , "inputs": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } - } - , "references": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } - } - , "collaterals": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } - } - , "totalCollateral": - { "$ref": "cardano.json#/definitions/Lovelace" - } - , "collateralReturn": - { "$ref": "cardano.json#/definitions/TransactionOutput" - } - , "outputs": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/TransactionOutput" } - } - , "certificates": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Certificate" } - } - , "withdrawals": - { "$ref": "cardano.json#/definitions/Withdrawals" - } - , "fee": - { "$ref": "cardano.json#/definitions/Lovelace" - } - , "validityInterval": - { "$ref": "cardano.json#/definitions/ValidityInterval" - } - , "mint": - { "$ref": "cardano.json#/definitions/Assets" - } - , "network": - { "$ref": "cardano.json#/definitions/Network" - } - , "scriptIntegrityHash": - { "$ref": "cardano.json#/definitions/Digest" - } - , "requiredExtraSignatories": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Digest" } - } - , "requiredExtraScripts": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Digest" } - } - , "governanceActions": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/GovernanceAction" } - } - , "metadata": - { "$ref": "cardano.json#/definitions/Metadata" - } - , "signatories": - { "type": "array" - , "items": { "$ref": "cardano.json#/definitions/Signatory" } - } - , "scripts": - { "type": "object" - , "propertyNames": { "contentEncoding": "base16", "pattern": "^[0-9a-f]+$" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Script" } - } - , "datums": - { "type": "object" - , "propertyNames": { "contentEncoding": "base16", "pattern": "^[0-9a-f]+$" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Datum" } - } - , "redeemers": - { "type": "object" - , "propertyNames": { "$ref": "cardano.json#/definitions/RedeemerPointer" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/Redeemer" } - } - , "cbor": - { "type": "string" - , "contentEncoding": "base16" - , "description": "The raw serialized (CBOR) transaction, as found on-chain." - } - } - } - - , "TransactionId": - { "title": "TransactionId" - , "description": "A Blake2b 32-byte hash digest of a transaction body" - , "type": "string" - , "contentEncoding": "base16" - , "minLength": 64 - , "maxLength": 64 - } - - , "TransactionOutput": - { "title": "TransactionOutput" - , "description": "A transaction output. Since Mary, 'value' always return a multi-asset value. Since Alonzo, 'datumHash' is always present (albeit sometimes 'null'). Since Babbage, 'datum' & 'script' are always present (albeit sometimes 'null')." - , "type": "object" - , "examples": - [ { "address": "addr_test1qz66ue36465w2qq40005h2hadad6pnjht8mu6sgplsfj74qdjnshguewlx4ww0eet26y2pal4xpav5prcydf28cvxtjqx46x7f" - , "value": - { "coins": 2 - , "assets": - { "3542acb3a64d80c29302260d62c3b87a742ad14abf855ebc6733081e": 42 - , "b5ae663aaea8e500157bdf4baafd6f5ba0ce5759f7cd4101fc132f54.706174617465": 1337 - } - } - , "datumHash": null - , "datum": null - , "script": null - } - ] - , "additionalProperties": false - , "required": [ "address", "value" ] - , "properties": - { "address": { "$ref": "cardano.json#/definitions/Address" } - , "value": { "$ref": "cardano.json#/definitions/Value" } - , "datumHash": { "$ref": "cardano.json#/definitions/Digest" } - , "datum": { "$ref": "cardano.json#/definitions/Datum" } - , "script": { "$ref": "cardano.json#/definitions/Script" } - } - } - - , "TransactionOutputReference": - { "title": "TransactionOutputReference" - , "type": "object" - , "additionalProperties": false - , "required": [ "transaction", "output" ] - , "properties": - { "transaction": - { "type": "object" - , "additionalProperties": false - , "required": [ "id" ] - , "properties": - { "id": - { "$ref": "cardano.json#/definitions/TransactionId" - } - } - } - , "output": - { "$ref": "cardano.json#/definitions/Index" - } - } - } - - , "UInt8": - { "title": "UInt8" - , "type": "integer" - , "minimum": 0 - , "maximum": 255 - } - - , "UInt32": - { "title": "UInt32" - , "type": "integer" - , "minimum": 0 - , "maximum": 4294967295 - } - - , "UInt64": - { "title": "UInt64" - , "type": "integer" - , "minimum": 0 - , "maximum": 18446744073709552999 - } - - , "UtcTime": - { "title": "UtcTime" - , "type": "string" - , "format": "date-time" - , "pattern": "[0-9]{4}-[0-9]{2}-[0-9]{2}T[0-9]{2}:[0-9]{2}:[0-9]{2}.?[0-9]*Z?" - } - - , "Utxo": - { "title": "Utxo" - , "type": "object" - , "propertyNames": - { "pattern": "^[0-9a-f]{64}#[0-9]+$" } - , "items": { "$ref": "cardano.json#/definitions/TransactionOutput" } - , "example": - { "09d34606abdcd0b10ebc89307cbfa0b469f9144194137b45b7a04b273961add8#687": - { "address": "addr1w9htvds89a78ex2uls5y969ttry9s3k9etww0staxzndwlgmzuul5" - , "value": - { "lovelace": 7620669 } - } - } - } - - , "ValidityInterval": - { "title": "ValidityInterval" - , "type": "object" - , "additionalProperties": false - , "properties": - { "invalidBefore": { "$ref": "cardano.json#/definitions/Slot" } - , "invalidAfter": { "$ref": "cardano.json#/definitions/Slot" } - } - } - - , "Value": - { "title": "Value" - , "type": "object" - , "propertyNames": { "pattern": "^[0-9a-z]{56}$" } - , "additionalProperties": - { "type": "object" - , "propertyNames": { "pattern": "^[0-9a-z]{0,64}$" } - , "additionalProperties": { "$ref": "cardano.json#/definitions/AssetQuantity" } - } - , "required": [ "ada" ] - , "properties": - { "ada": - { "type": "object" - , "additionalProperties": false - , "required": [ "lovelace" ] - , "properties": - { "lovelace": { "type": "integer" } - } - } - } - } - - , "VerificationKey": - { "title": "VerificationKey" - , "description": "An Ed25519 verification key." - , "type": "string" - , "contentEncoding": "base16" - , "minLength": 64 - , "maxLength": 64 - } - - , "VoterRole": - { "title": "VoterRole" - , "type": "string" - , "enum": [ "constitutionalCommittee", "delegateRepresentative", "stakePoolOperator" ] - } - - , "VotingPeriod": - { "title": "VotingPeriod" - , "type": "string" - , "enum": [ "voteForThisEpoch", "voteForNextEpoch" ] - } - - , "VrfProof": - { "title": "VrfProof" - , "type": "string" - , "contentEncoding": "base16" - } - - , "VrfOutput": - { "title": "VrfOutput" - , "type": "string" - , "contentEncoding": "base16" - } - - , "Withdrawals": - { "title": "Withdrawals" - , "type": "object" - , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } - , "propertyNames": { "pattern": "^stake(_test)?1[0-9a-z]+$" } - } - } -} From 57dc921c3baa5b18786bf47bf55ba7a3846baca0 Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 08:10:31 +0100 Subject: [PATCH 05/11] Fix validateJSON to resolve references We need to copy the schema files correctly into the temporary working directory of validateJSON. --- hydra-node/test/Hydra/JSONSchema.hs | 25 ++++++++++++++++++------- hydra-node/test/Hydra/JSONSchemaSpec.hs | 8 ++++++++ 2 files changed, 26 insertions(+), 7 deletions(-) diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/test/Hydra/JSONSchema.hs index 484a234fce1..71e1712ff9f 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/test/Hydra/JSONSchema.hs @@ -18,9 +18,9 @@ import Data.Text (pack) import Data.Versions (SemVer (SemVer), prettySemVer, semver) import Data.Yaml qualified as Yaml import Paths_hydra_node qualified as Pkg -import System.Directory (listDirectory) +import System.Directory (copyFile, listDirectory) import System.Exit (ExitCode (..)) -import System.FilePath (normalise, takeBaseName, takeExtension, (<.>), ()) +import System.FilePath (normalise, takeBaseName, takeDirectory, takeExtension, takeFileName, (<.>), ()) import System.IO.Error (IOError, isDoesNotExistError) import System.Process (readProcessWithExitCode) import Test.QuickCheck (Property, counterexample, forAllShrink, resize, vectorOf) @@ -55,19 +55,23 @@ validateJSON :: SchemaSelector -> Value -> IO () -validateJSON schemaFilePath selector value = +validateJSON schemaFilePath selector value = do + ensureSystemRequirements withTempDir "validateJSON" $ \tmpDir -> do - ensureSystemRequirements - let jsonInput = tmpDir "jsonInput" - let jsonSchema = tmpDir "jsonSchema" + copySchemasTo tmpDir + -- Write input file + let jsonInput = tmpDir "input.json" + writeFileLBS jsonInput (Aeson.encode value) + -- Write (sub-)schema to use + let jsonSchema = tmpDir "schema.json" Aeson.eitherDecodeFileStrict schemaFilePath >>= \case Left err -> fail $ "Failed to decode JSON schema " <> show schemaFilePath <> ": " <> err Right schemaValue -> do let jsonSpecSchema = schemaValue ^? selector <&> addField "$id" ("file://" <> tmpDir <> "/") - writeFileLBS jsonInput (Aeson.encode value) writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) + -- Validate using external program (exitCode, out, err) <- readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] "" when (exitCode /= ExitSuccess) $ @@ -77,6 +81,13 @@ validateJSON schemaFilePath selector value = , toText out , toText err ] + where + copySchemasTo dir = do + let sourceDir = takeDirectory schemaFilePath + files <- listDirectory sourceDir + let schemaFiles = filter (\fp -> takeExtension fp `elem` [".json", ".yaml"]) files + forM_ schemaFiles $ \fp -> + copyFile (sourceDir fp) (dir takeFileName fp) -- | Validate an 'Arbitrary' value against a JSON schema. -- diff --git a/hydra-node/test/Hydra/JSONSchemaSpec.hs b/hydra-node/test/Hydra/JSONSchemaSpec.hs index 3c666508a88..523415bab7e 100644 --- a/hydra-node/test/Hydra/JSONSchemaSpec.hs +++ b/hydra-node/test/Hydra/JSONSchemaSpec.hs @@ -41,3 +41,11 @@ spec = (object ["foo" .= String "bar"]) `shouldThrow` exceptionContaining @HUnitFailure "{'foo': 'bar'} is not of type 'string'" + + it "resolves refs" $ + withJsonSpecifications $ \dir -> + validateJSON + (dir "api.json") + -- NOTE: MultiSignature has a local ref into api.yaml for Signature + (key "components" . key "schemas" . key "MultiSignature") + (object ["multiSignature" .= [String "bar"]]) From 57e4b4d56997e71b7fa42bca759dae872d36734d Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 09:43:20 +0100 Subject: [PATCH 06/11] Revert "Remove unused vendored cardano.json schema" This reverts commit fcb02e1770c74169af85abee67f1d1c3013e1654. --- hydra-node/json-schemas/cardanonical/LICENSE | 201 ++ .../json-schemas/cardanonical/cardano.json | 1969 +++++++++++++++++ 2 files changed, 2170 insertions(+) create mode 100644 hydra-node/json-schemas/cardanonical/LICENSE create mode 100644 hydra-node/json-schemas/cardanonical/cardano.json diff --git a/hydra-node/json-schemas/cardanonical/LICENSE b/hydra-node/json-schemas/cardanonical/LICENSE new file mode 100644 index 00000000000..261eeb9e9f8 --- /dev/null +++ b/hydra-node/json-schemas/cardanonical/LICENSE @@ -0,0 +1,201 @@ + Apache License + Version 2.0, January 2004 + http://www.apache.org/licenses/ + + TERMS AND CONDITIONS FOR USE, REPRODUCTION, AND DISTRIBUTION + + 1. Definitions. + + "License" shall mean the terms and conditions for use, reproduction, + and distribution as defined by Sections 1 through 9 of this document. + + "Licensor" shall mean the copyright owner or entity authorized by + the copyright owner that is granting the License. + + "Legal Entity" shall mean the union of the acting entity and all + other entities that control, are controlled by, or are under common + control with that entity. For the purposes of this definition, + "control" means (i) the power, direct or indirect, to cause the + direction or management of such entity, whether by contract or + otherwise, or (ii) ownership of fifty percent (50%) or more of the + outstanding shares, or (iii) beneficial ownership of such entity. + + "You" (or "Your") shall mean an individual or Legal Entity + exercising permissions granted by this License. + + "Source" form shall mean the preferred form for making modifications, + including but not limited to software source code, documentation + source, and configuration files. + + "Object" form shall mean any form resulting from mechanical + transformation or translation of a Source form, including but + not limited to compiled object code, generated documentation, + and conversions to other media types. + + "Work" shall mean the work of authorship, whether in Source or + Object form, made available under the License, as indicated by a + copyright notice that is included in or attached to the work + (an example is provided in the Appendix below). + + "Derivative Works" shall mean any work, whether in Source or Object + form, that is based on (or derived from) the Work and for which the + editorial revisions, annotations, elaborations, or other modifications + represent, as a whole, an original work of authorship. For the purposes + of this License, Derivative Works shall not include works that remain + separable from, or merely link (or bind by name) to the interfaces of, + the Work and Derivative Works thereof. + + "Contribution" shall mean any work of authorship, including + the original version of the Work and any modifications or additions + to that Work or Derivative Works thereof, that is intentionally + submitted to Licensor for inclusion in the Work by the copyright owner + or by an individual or Legal Entity authorized to submit on behalf of + the copyright owner. For the purposes of this definition, "submitted" + means any form of electronic, verbal, or written communication sent + to the Licensor or its representatives, including but not limited to + communication on electronic mailing lists, source code control systems, + and issue tracking systems that are managed by, or on behalf of, the + Licensor for the purpose of discussing and improving the Work, but + excluding communication that is conspicuously marked or otherwise + designated in writing by the copyright owner as "Not a Contribution." + + "Contributor" shall mean Licensor and any individual or Legal Entity + on behalf of whom a Contribution has been received by Licensor and + subsequently incorporated within the Work. + + 2. Grant of Copyright License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + copyright license to reproduce, prepare Derivative Works of, + publicly display, publicly perform, sublicense, and distribute the + Work and such Derivative Works in Source or Object form. + + 3. Grant of Patent License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + (except as stated in this section) patent license to make, have made, + use, offer to sell, sell, import, and otherwise transfer the Work, + where such license applies only to those patent claims licensable + by such Contributor that are necessarily infringed by their + Contribution(s) alone or by combination of their Contribution(s) + with the Work to which such Contribution(s) was submitted. If You + institute patent litigation against any entity (including a + cross-claim or counterclaim in a lawsuit) alleging that the Work + or a Contribution incorporated within the Work constitutes direct + or contributory patent infringement, then any patent licenses + granted to You under this License for that Work shall terminate + as of the date such litigation is filed. + + 4. Redistribution. You may reproduce and distribute copies of the + Work or Derivative Works thereof in any medium, with or without + modifications, and in Source or Object form, provided that You + meet the following conditions: + + (a) You must give any other recipients of the Work or + Derivative Works a copy of this License; and + + (b) You must cause any modified files to carry prominent notices + stating that You changed the files; and + + (c) You must retain, in the Source form of any Derivative Works + that You distribute, all copyright, patent, trademark, and + attribution notices from the Source form of the Work, + excluding those notices that do not pertain to any part of + the Derivative Works; and + + (d) If the Work includes a "NOTICE" text file as part of its + distribution, then any Derivative Works that You distribute must + include a readable copy of the attribution notices contained + within such NOTICE file, excluding those notices that do not + pertain to any part of the Derivative Works, in at least one + of the following places: within a NOTICE text file distributed + as part of the Derivative Works; within the Source form or + documentation, if provided along with the Derivative Works; or, + within a display generated by the Derivative Works, if and + wherever such third-party notices normally appear. The contents + of the NOTICE file are for informational purposes only and + do not modify the License. You may add Your own attribution + notices within Derivative Works that You distribute, alongside + or as an addendum to the NOTICE text from the Work, provided + that such additional attribution notices cannot be construed + as modifying the License. + + You may add Your own copyright statement to Your modifications and + may provide additional or different license terms and conditions + for use, reproduction, or distribution of Your modifications, or + for any such Derivative Works as a whole, provided Your use, + reproduction, and distribution of the Work otherwise complies with + the conditions stated in this License. + + 5. Submission of Contributions. Unless You explicitly state otherwise, + any Contribution intentionally submitted for inclusion in the Work + by You to the Licensor shall be under the terms and conditions of + this License, without any additional terms or conditions. + Notwithstanding the above, nothing herein shall supersede or modify + the terms of any separate license agreement you may have executed + with Licensor regarding such Contributions. + + 6. Trademarks. This License does not grant permission to use the trade + names, trademarks, service marks, or product names of the Licensor, + except as required for reasonable and customary use in describing the + origin of the Work and reproducing the content of the NOTICE file. + + 7. Disclaimer of Warranty. Unless required by applicable law or + agreed to in writing, Licensor provides the Work (and each + Contributor provides its Contributions) on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or + implied, including, without limitation, any warranties or conditions + of TITLE, NON-INFRINGEMENT, MERCHANTABILITY, or FITNESS FOR A + PARTICULAR PURPOSE. You are solely responsible for determining the + appropriateness of using or redistributing the Work and assume any + risks associated with Your exercise of permissions under this License. + + 8. Limitation of Liability. In no event and under no legal theory, + whether in tort (including negligence), contract, or otherwise, + unless required by applicable law (such as deliberate and grossly + negligent acts) or agreed to in writing, shall any Contributor be + liable to You for damages, including any direct, indirect, special, + incidental, or consequential damages of any character arising as a + result of this License or out of the use or inability to use the + Work (including but not limited to damages for loss of goodwill, + work stoppage, computer failure or malfunction, or any and all + other commercial damages or losses), even if such Contributor + has been advised of the possibility of such damages. + + 9. Accepting Warranty or Additional Liability. While redistributing + the Work or Derivative Works thereof, You may choose to offer, + and charge a fee for, acceptance of support, warranty, indemnity, + or other liability obligations and/or rights consistent with this + License. However, in accepting such obligations, You may act only + on Your own behalf and on Your sole responsibility, not on behalf + of any other Contributor, and only if You agree to indemnify, + defend, and hold each Contributor harmless for any liability + incurred by, or claims asserted against, such Contributor by reason + of your accepting any such warranty or additional liability. + + END OF TERMS AND CONDITIONS + + APPENDIX: How to apply the Apache License to your work. + + To apply the Apache License to your work, attach the following + boilerplate notice, with the fields enclosed by brackets "[]" + replaced with your own identifying information. (Don't include + the brackets!) The text should be enclosed in the appropriate + comment syntax for the file format. We also recommend that a + file or class name and description of purpose be included on the + same "printed page" as the copyright notice for easier + identification within third-party archives. + + Copyright [yyyy] [name of copyright owner] + + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. diff --git a/hydra-node/json-schemas/cardanonical/cardano.json b/hydra-node/json-schemas/cardanonical/cardano.json new file mode 100644 index 00000000000..fe64801ea59 --- /dev/null +++ b/hydra-node/json-schemas/cardanonical/cardano.json @@ -0,0 +1,1969 @@ +{ "$schema": "https://json-schema.org/draft-07/schema" +, "$id": "cardano.json" +, "title": "Cardano" +, "definitions": + { "Address": + { "title": "Address" + , "type": "string" + , "description": "A Cardano address (either legacy format or new format)." + , "contentEncoding": "bech32|base58" + , "pattern": "[1-9A-HJ-NP-Za-km-z]*" + , "examples": + [ "addr1q9d34spgg2kdy47n82e7x9pdd6vql6d2engxmpj20jmhuc2047yqd4xnh7u6u5jp4t0q3fkxzckph4tgnzvamlu7k5psuahzcp" + , "DdzFFzCqrht8mbSTZHqpM2u4HeND2mdspsaBhdQ1BowPJBMzbDeBMeKgqdoKqo1D4sdPusEdZJVrFJRBBxX1jUEofNDYCJSZLg8MkyCE" + ] + } + + , "AddressAttributes": + { "title": "AddressAttributes" + , "type": "string" + , "description": "Extra attributes carried by Byron addresses (network magic and/or HD payload)." + , "contentEncoding": "base16" + } + + , "AssetQuantity": + { "title": "AssetQuantity" + , "type": "integer" + , "description": "A number of asset, can be negative went burning assets." + } + + , "Assets": + { "title": "Assets" + , "type": "object" + , "propertyNames": { "pattern": "^[0-9a-z]{56}$" } + , "additionalProperties": + { "type": "object" + , "propertyNames": { "pattern": "^[0-9a-z]{0,64}$" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/AssetQuantity" } + } + } + + , "Block": + { "title": "Block" + , "oneOf": + [ { "$ref": "cardano.json#/definitions/Block" } + , { "$ref": "cardano.json#/definitions/Block" } + , { "$ref": "cardano.json#/definitions/Block" } + ] + } + + , "Block": + { "title": "Block" + , "type": "object" + , "additionalProperties": false + , "required": + [ "id", "type", "era", "ancestor", "height" + ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "ebb" ] + } + , "era": + { "type": "string" + , "enum": [ "byron" ] + } + , "id": { "$ref": "cardano.json#/definitions/Digest" } + , "ancestor": { "$ref": "cardano.json#/definitions/Digest" } + , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } + } + } + + , "Block": + { "title": "Block" + , "type": "object" + , "additionalProperties": false + , "required": + [ "id", "era", "type", "ancestor", "height", "size", "slot" + , "protocol", "issuer", "delegate" + ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "bft" ] + } + , "era": + { "type": "string" + , "enum": [ "byron" ] + } + , "id": { "$ref": "cardano.json#/definitions/Digest" } + , "ancestor": { "$ref": "cardano.json#/definitions/Digest" } + , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } + , "slot": { "$ref": "cardano.json#/definitions/Slot" } + , "size": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "transactions": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Transaction" } + } + , "operationalCertificates": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/BootstrapOperationalCertificate"} + } + , "protocol": + { "type": "object" + , "additionalProperties": false + , "required": [ "id", "version", "software" ] + , "properties": + { "id": { "$ref": "cardano.json#/definitions/BootstrapProtocolId" } + , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } + , "software": { "$ref": "cardano.json#/definitions/SoftwareVersion" } + , "update": { "$ref": "cardano.json#/definitions/BootstrapProtocolUpdate" } + } + } + , "issuer": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/ExtendedVerificationKey" } + } + } + , "delegate": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/ExtendedVerificationKey" } + } + } + } + } + + , "Block": + { "title": "Block" + , "type": "object" + , "additionalProperties": false + , "required": + [ "id", "era", "type", "ancestor", "height", "size", "slot" + , "protocol", "issuer" + ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "praos" ] + } + , "era": + { "type": "string" + , "enum": [ "shelley", "allegra", "mary", "alonzo", "babbage" ] + } + , "id": { "$ref": "cardano.json#/definitions/Digest" } + , "ancestor": + { "oneOf": + [ { "$ref": "cardano.json#/definitions/Digest" } + , { "title": "GenesisHash", "type": "string", "enum": [ "genesis" ] } + ] + } + , "nonce": { "$ref": "cardano.json#/definitions/CertifiedVrf" } + , "height": { "$ref": "cardano.json#/definitions/BlockHeight" } + , "size": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "slot": { "$ref": "cardano.json#/definitions/Slot" } + , "transactions": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Transaction" } + } + , "protocol": + { "type": "object" + , "additionalProperties": false + , "required": [ "version" ] + , "properties": + { "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } + } + } + , "issuer": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey", "vrfVerificationKey", "operationalCertificate", "leaderValue" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } + , "vrfVerificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } + , "operationalCertificate": { "$ref": "cardano.json#/definitions/OperationalCertificate" } + , "leaderValue": { "$ref": "cardano.json#/definitions/CertifiedVrf" } + } + } + } + } + + , "BlockHeight": + { "title": "BlockHeight" + , "type": "integer" + , "description": "A block number, the i-th block to be minted is number i." + , "minimum": 0 + , "maximum": 18446744073709552999 + } + + , "BootstrapProtocolUpdate": + { "title": "BootstrapProtocolUpdate" + , "type": "object" + , "additionalProperties": false + , "required": [ "votes" ] + , "properties": + { "proposal": + { "type": "object" + , "additionalProperties": false + , "required": [ "version", "software", "parameters", "metadata" ] + , "properties": + { "version": + { "$ref": "cardano.json#/definitions/ProtocolVersion" + } + , "software": + { "$ref": "cardano.json#/definitions/SoftwareVersion" + } + , "parameters": + { "$ref": "cardano.json#/definitions/BootstrapProtocolParameters" + } + , "metadata": + { "type": "object" + , "additionalProperties": { "type": "string" } + } + } + } + , "votes": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/BootstrapVote" } + } + } + } + + , "BootstrapOperationalCertificate": + { "title": "BootstrapOperationalCertificate" + , "type": "object" + , "description": "A (Byron) delegation certificate." + , "additionalProperties": false + , "required": [ "issuer", "delegate" ] + , "properties": + { "issuer": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } + } + } + , "delegate": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } + } + } + } + } + + , "BootstrapProtocolId": + { "title": "BootstrapProtocolId" + , "type": "integer" + , "minimum": 0 + , "maximum": 4294967295 + , "examples": + [ 764824073 + ] + } + + , "BootstrapProtocolParameters": + { "title": "BootstrapProtocolParameters" + , "type": "object" + , "additionalProperties": false + , "properties": + { "heavyDelegationThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxUpdateProposalSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "multiPartyComputationThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "scriptVersion": { "$ref": "cardano.json#/definitions/UInt64" } + , "slotDuration": { "$ref": "cardano.json#/definitions/UInt64" } + , "unlockStakeEpoch": { "$ref": "cardano.json#/definitions/UInt64" } + , "updateProposalThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "updateProposalTimeToLive": { "$ref": "cardano.json#/definitions/UInt64" } + , "updateVoteThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "softForkInitThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "softForkMinThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "softForkDecrementThreshold": { "$ref": "cardano.json#/definitions/Ratio" } + , "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } + } + } + + , "BootstrapVote": + { "title": "BootstrapVote" + , "type": "object" + , "additionalProperties": false + , "required": [ "voter", "proposal" ] + , "properties": + { "voter": + { "type": "object" + , "additionalProperties": false + , "required": [ "verificationKey" ] + , "properties": + { "verificationKey": { "$ref": "cardano.json#/definitions/VerificationKey" } + } + } + , "proposal": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": { "$ref": "cardano.json#/definitions/Digest" } + } + } + } + } + + , "Bound": + { "title": "Bound" + , "type": "object" + , "description": "An era bound which captures the time, slot and epoch at which the era start. The time is relative to the start time of the network." + , "additionalProperties": false + , "required": ["time", "slot", "epoch"] + , "properties": + { "time": { "$ref": "cardano.json#/definitions/RelativeTime" } + , "slot": { "$ref": "cardano.json#/definitions/Slot" } + , "epoch": { "$ref": "cardano.json#/definitions/Epoch" } + } + } + + , "Certificate": + { "title": "Certificate" + , "oneOf": + [ { "type": "object" + , "description": "A stake delegation certificate, from a delegator to a stake pool." + , "title": "stakeDelegation" + , "additionalProperties": false + , "required": [ "type", "credential", "stakePool" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "stakeDelegation" ] + } + , "credential": + { "$ref": "cardano.json#/definitions/Digest" + } + , "stakePool": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/StakePoolId" + } + } + } + } + } + , { "type": "object" + , "description": "A stake credential (key or script) registration certificate." + , "title": "stakeCredentialRegistration" + , "additionalProperties": false + , "required": [ "type", "credential" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "stakeCredentialRegistration" ] + } + , "credential": + { "$ref": "cardano.json#/definitions/Digest" + } + } + } + , { "type": "object" + , "description": "A stake key de-registration certificate." + , "title": "stakeCredentialDeregistration" + , "additionalProperties": false + , "required": [ "type", "credential" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "stakeCredentialDeregistration" ] + } + , "credential": + { "$ref": "cardano.json#/definitions/Digest" + } + } + } + , { "type": "object" + , "description": "A stake pool registration certificate." + , "title": "stakePoolRegistration" + , "additionalProperties": false + , "required": [ "type", "stakePool" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "stakePoolRegistration" ] + } + , "stakePool": + { "$ref": "cardano.json#/definitions/StakePool" + } + } + } + , { "type": "object" + , "description": "A stake pool retirement certificate." + , "additionalProperties": false + , "title": "stakePoolRetirement" + , "required": [ "type", "stakePool"] + , "properties": + { "type": + { "type": "string" + , "enum": [ "stakePoolRetirement" ] + } + , "stakePool": + { "type": "object" + , "additionalProperties": false + , "required": [ "id", "retirementEpoch" ] + , "properties": + { "retirementEpoch": { "$ref": "cardano.json#/definitions/Epoch" } + , "id": { "$ref": "cardano.json#/definitions/StakePoolId" } + } + } + } + } + , { "type": "object" + , "title": "genesisDelegation" + , "additionalProperties": false + , "required": [ "type", "delegate", "issuer" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "genesisDelegation" ] + } + , "delegate": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/Digest" + } + } + } + , "issuer": + { "type": "object" + , "additionalProperties": false + , "required": [ "id", "vrfVerificationKeyHash" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/Digest" + } + , "vrfVerificationKeyHash": + { "$ref": "cardano.json#/definitions/Digest" + } + } + } + } + } + , { "title": "TreasuryTransfer" + , "oneOf": + [ { "type": "object" + , "title": "TreasuryTransfer" + , "description": "A transfer from or to the treasury / reserves authored by genesis delegates." + , "additionalProperties": false + , "required": [ "type", "source", "target", "value" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "treasuryTransfer" ] + } + , "source": + { "type": "string" + , "enum": [ "reserves", "treasury" ] + } + , "target": + { "type": "string" + , "enum": [ "reserves", "treasury" ] + } + , "value": + { "$ref": "cardano.json#/definitions/Lovelace" + } + } + } + , { "type": "object" + , "title": "TreasuryTransfer" + , "description": "A transfer from or to the treasury / reserves authored by genesis delegates." + , "additionalProperties": false + , "required": [ "type", "source", "target", "rewards" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "treasuryTransfer" ] + } + , "source": + { "type": "string" + , "enum": [ "reserves", "treasury" ] + } + , "target": + { "type": "string" + , "enum": [ "rewardAccounts" ] + } + , "rewards": + { "$ref": "cardano.json#/definitions/RewardTransfer" + } + } + } + ] + } + ] + } + + , "CertifiedVrf": + { "title": "CertifiedVrf" + , "type": "object" + , "additionalProperties": false + , "properties": + { "proof": { "$ref": "cardano.json#/definitions/VrfProof" } + , "output": { "$ref": "cardano.json#/definitions/VrfOutput" } + } + } + + , "ChainCode": + { "title": "ChainCode" + , "type": "string" + , "description": "An Ed25519-BIP32 chain-code for key deriviation." + , "contentEncoding": "base16" + } + + , "CostModels": + { "title": "CostModels" + , "type": "object" + , "additionalProperties": { "$ref": "cardano.json#/definitions/CostModel" } + , "propertyNames": { "$ref": "cardano.json#/definitions/Language" } + , "examples": + [ { "plutus:v1": + { "k": 14 + , "a": 123 + } + } + ] + } + + , "CostModel": + { "title": "CostModel" + , "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Int64" } + } + + , "Datum": + { "title": "Datum" + , "type": "string" + , "contentEncoding": "base16" + } + + , "Digest": + { "title": "Digest" + , "type": "string" + , "description": "A hash digest from an unspecified algorithm and length." + , "contentEncoding": "base16" + , "examples": + [ "90181c517a5beadc9c3fe64bf8" + ] + } + + , "Digest": + { "title": "Digest" + , "type": "string" + , "description": "A Blake2b 28-byte hash digest, encoded in base16." + , "contentEncoding": "base16" + , "minLength": 56 + , "maxLength": 56 + , "examples": + [ "90181c517a5beadc9c3fe64bf821d3e889a963fc717003ec248757d3" + ] + } + + , "Digest": + { "title": "Digest" + , "type": "string" + , "description": "A Blake2b 32-byte hash digest, encoded in base16." + , "contentEncoding": "base16" + , "minLength": 64 + , "maxLength": 64 + , "examples": + [ "c248757d390181c517a5beadc9c3fe64bf821d3e889a963fc717003ec248757d" + ] + } + + , "Epoch": + { "title": "Epoch" + , "type": "integer" + , "description": "An epoch number or length." + , "minimum": 0 + , "maximum": 18446744073709552000 + } + + , "Era": + { "title": "Era" + , "type": "string" + , "enum": [ "byron", "shelley", "allegra", "mary", "alonzo", "babbage", "conway" ] + } + + , "EraWithGenesis": + { "title": "EraWithGenesis" + , "type": "string" + , "enum": [ "byron", "shelley", "alonzo", "conway" ] + } + + , "EraParameters": + { "title": "EraParameters" + , "type": "object" + , "description": "Parameters that can vary across hard forks." + , "additionalProperties": false + , "required": [ "epochLength", "slotLength", "safeZone" ] + , "properties": + { "epochLength": { "$ref": "cardano.json#/definitions/Epoch" } + , "slotLength": { "$ref": "cardano.json#/definitions/SlotLength" } + , "safeZone": + { "oneOf": + [ { "$ref": "cardano.json#/definitions/SafeZone" } + , { "type": "null" } + ] + } + } + } + + , "EraSummary": + { "title": "EraSummary" + , "type": "object" + , "description": "Summary of the confirmed parts of the ledger." + , "additionalProperties": false + , "required": [ "start", "parameters" ] + , "properties": + { "start": { "$ref": "cardano.json#/definitions/Bound" } + , "end": { "$ref": "cardano.json#/definitions/Bound" } + , "parameters": { "$ref": "cardano.json#/definitions/EraParameters" } + } + } + + , "ExecutionUnits": + { "title": "ExecutionUnits" + , "type": "object" + , "additionalProperties": false + , "required": [ "memory", "cpu" ] + , "properties": + { "memory": { "$ref": "cardano.json#/definitions/UInt64" } + , "cpu": { "$ref": "cardano.json#/definitions/UInt64" } + } + } + + , "Genesis": + { "title": "Genesis" + , "type": "object" + , "description": "A Byron genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." + , "additionalProperties": false + , "required": + [ "era" + , "genesisKeyHashes" + , "genesisDelegations" + , "startTime" + , "initialFunds" + , "initialVouchers" + , "securityParameter" + , "networkMagic" + , "protocolParameters" + ] + , "properties": + { "era": + { "type": "string" + , "enum": [ "byron" ] + } + , "genesisKeyHashes": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Digest" } + } + , "genesisDelegations": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/Digest" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/BootstrapOperationalCertificate" } + } + , "startTime": { "$ref": "cardano.json#/definitions/UtcTime" } + , "initialFunds": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/Address" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } + } + , "initialVouchers": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/VerificationKey" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } + } + , "securityParameter": { "$ref": "cardano.json#/definitions/UInt64" } + , "networkMagic": { "$ref": "cardano.json#/definitions/NetworkMagic" } + , "protocolParameters": { "$ref": "cardano.json#/definitions/ProtocolParameters" } + } + } + + , "Genesis": + { "title": "Genesis" + , "type": "object" + , "description": "A Shelley genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." + , "additionalProperties": false + , "required": + [ "era" + , "startTime" + , "networkMagic" + , "network" + , "activeSlotsCoefficient" + , "securityParameter" + , "epochLength" + , "slotsPerKesPeriod" + , "maxKesEvolutions" + , "slotLength" + , "updateQuorum" + , "maxLovelaceSupply" + , "initialParameters" + , "initialDelegates" + , "initialFunds" + , "initialStakePools" + ] + , "properties": + { "era": + { "type": "string" + , "enum": [ "shelley" ] + } + , "startTime": { "$ref": "cardano.json#/definitions/UtcTime" } + , "networkMagic": { "$ref": "cardano.json#/definitions/NetworkMagic" } + , "network": { "$ref": "cardano.json#/definitions/Network" } + , "activeSlotsCoefficient": { "$ref": "cardano.json#/definitions/Ratio" } + , "securityParameter": { "$ref": "cardano.json#/definitions/UInt64" } + , "epochLength": { "$ref": "cardano.json#/definitions/Epoch" } + , "slotsPerKesPeriod": { "$ref": "cardano.json#/definitions/UInt64" } + , "maxKesEvolutions": { "$ref": "cardano.json#/definitions/UInt64" } + , "slotLength": { "$ref": "cardano.json#/definitions/SlotLength" } + , "updateQuorum": { "$ref": "cardano.json#/definitions/UInt64" } + , "maxLovelaceSupply": { "$ref": "cardano.json#/definitions/UInt64" } + , "initialParameters": { "$ref": "cardano.json#/definitions/ProtocolParameters" } + , "initialDelegates": { "$ref": "cardano.json#/definitions/InitialDelegates" } + , "initialFunds": + { "type": "object" + , "title": "InitialFunds" + , "propertyNames": { "$ref": "cardano.json#/definitions/Address" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } + } + , "initialStakePools": { "$ref": "cardano.json#/definitions/GenesisStakePools" } + } + } + + , "Genesis": + { "title": "Genesis" + , "type": "object" + , "description": "An Alonzo genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." + , "additionalProperties": false + , "required": + [ "era" + , "initialParameters" + ] + , "properties": + { "era": + { "type": "string" + , "enum": [ "alonzo" ] + } + , "initialParameters": + { "type": "object" + , "additionalProperties": false + , "required": + [ "minUtxoDepositCoefficient" + , "collateralPercentage" + , "plutusCostModels" + , "maxCollateralInputs" + , "maxExecutionUnitsPerBlock" + , "maxExecutionUnitsPerTransaction" + , "maxValueSize" + , "scriptExecutionPrices" + ] + , "properties": + { "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } + , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } + , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } + , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } + } + } + } + } + + , "Genesis": + { "title": "Genesis" + , "type": "object" + , "description": "An Conway genesis configuration, with information used to bootstrap the era. Some parameters are also updatable across the era." + , "additionalProperties": false + , "required": + [ "era" + , "initialDelegates" + ] + , "properties": + { "era": + { "type": "string" + , "enum": [ "conway" ] + } + , "initialDelegates": + { "$ref": "cardano.json#/definitions/InitialDelegates" + } + } + } + + , "GenesisDelegate": + { "title": "GenesisDelegate" + , "type": "object" + , "description": "A Genesis delegate, in charge of Cardano's governance." + , "additionalProperties": false + , "required": + [ "vrfVerificationKeyHash" + , "id" + ] + , "properties": + { "id": { "$ref": "cardano.json#/definitions/Digest" } + , "vrfVerificationKeyHash": { "$ref": "cardano.json#/definitions/Digest" } + } + } + + , "GenesisStakePools": + { "title": "GenesisStakePools" + , "type": "object" + , "description": "A Genesis stake pools configuration; primarily used for bootstrapping test networks." + , "additionalProperties": false + , "required": + [ "stakePools" + , "delegators" + ] + , "properties": + { "stakePools": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/StakePoolId" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/StakePool" } + } + , "delegators": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/Digest" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/StakePoolId" } + } + } + } + + , "GovernanceAction": + { "oneOf": + [ { "title": "GovernanceAction" + , "type": "object" + , "additionalProperties": false + , "required": [ "type", "parameters" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "protocolParametersUpdate" ] + } + , "parameters": + { "$ref": "cardano.json#/definitions/ProposedProtocolParameters" + } + } + } + ] + } + + , "GovernanceActionReference": + { "title": "GovernanceActionReference" + , "type": "object" + , "additionalProperties": false + , "required": [ "transaction", "governanceAction" ] + , "properties": + { "transaction": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/TransactionId" + } + } + } + , "governanceAction": + { "$ref": "cardano.json#/definitions/Index" + } + } + } + + , "ExtendedVerificationKey": + { "title": "ExtendedVerificationKey" + , "type": "string" + , "description": "An Ed25519-BIP32 Byron genesis delegate verification key with chain-code." + , "contentEncoding": "base16" + , "minLength": 128 + , "maxLength": 128 + } + + , "Index": + { "type": "object" + , "additionalProperties": false + , "required": [ "index" ] + , "properties": + { "index": + { "$ref": "cardano.json#/definitions/UInt32" + } + } + } + + , "InitialDelegates": + { "title": "InitialDelegates" + , "type": "array" + , "items": + { "type": "object" + , "additionalProperties": false + , "required": [ "issuer", "delegate" ] + , "properties": + { "issuer": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": { "$ref": "cardano.json#/definitions/Digest" } + } + } + , "delegate": + { "$ref": "cardano.json#/definitions/GenesisDelegate" + } + } + } + } + + , "Int64": + { "title": "Int64" + , "type": "integer" + , "minimum": -9223372036854775808 + , "maximum": 9223372036854775807 + } + + , "InputSource": + { "type": "string" + , "enum": + [ "inputs" + , "collaterals" + ] + } + + , "Language": + { "title": "Language" + , "type": "string" + , "enum": [ "plutus:v1", "plutus:v2", "plutus:v3" ] + } + + , "Lovelace": + { "title": "Lovelace" + , "additionalProperties": false + , "required": [ "lovelace" ] + , "properties": + { "lovelace": + { "type": "integer" + , "description": "A number of lovelace, possibly large when summed up." + } + } + } + + , "LovelaceDelta": + { "title": "LovelaceDelta" + , "type": "object" + , "additionalProperties": false + , "required": [ "lovelace" ] + , "properties": + { "lovelace": + { "type": "integer" + , "description": "An amount, possibly negative, in Lovelace (1e6 Lovelace = 1 Ada)." + , "minimum": -9223372036854775808 + , "maximum": 9223372036854775807 + } + } + } + + , "KesVerificationKey": + { "title": "KesVerificationKey" + , "type": "string" + , "contentEncoding": "base16" + } + + , "Metadata": + { "title": "Metadata" + , "type": "object" + , "additionalProperties": false + , "required": [ "hash", "labels" ] + , "properties": + { "hash": { "$ref": "cardano.json#/definitions/Digest" } + , "labels": { "$ref": "cardano.json#/definitions/MetadataLabels" } + } + } + + , "MetadataLabels": + { "title": "MetadataLabels" + , "type": "object" + , "propertyNames": { "pattern": "^-?[0-9]+$" } + , "additionalProperties": + { "type": "object" + , "description": "An associated metadatum, as a CBOR bytestring or a JSON object if possible. Some binary representations cannot be represented in plain JSON and the 'json' field is therefore omitted." + , "required": [ "cbor" ] + , "additionalProperties": false + , "properties": + { "cbor": + { "type": "string" + , "contentEncoding": "base16" + , "pattern": "^[0-9a-f]*$" + } + , "json": + { "$ref": "cardano.json#/definitions/Metadatum" + } + } + } + } + + , "Metadatum": + { "title": "Metadatum" + , "oneOf": + [ { "title": "Integer", "type": "integer" } + , { "title": "String", "type": "string" } + , { "title": "Array", "type": "array", "items": { "$ref": "cardano.json#/definitions/Metadatum" } } + , { "title": "Object", "type": "object", "additionalProperties": { "$ref": "cardano.json#/definitions/Metadatum" } } + ] + } + + , "Network": + { "title": "Network" + , "type": "string" + , "description": "A network target, as defined since the Shelley era." + , "enum": [ "mainnet", "testnet" ] + } + + , "NetworkMagic": + { "title": "NetworkMagic" + , "type": "integer" + , "description": "A magic number for telling networks apart. (e.g. 764824073)" + , "minimum": 0 + , "maximum": 4294967296 + , "examples": + [ 764824073 + ] + } + + , "Nonce": + { "title": "Nonce" + , "oneOf": + [ { "type": "string" + , "enum": ["neutral"] + , "title": "neutral" + } + , { "$ref": "cardano.json#/definitions/Digest" } + ] + } + + , "Null": + { "type": "null" + } + + , "NumberOfBytes": + { "type": "object" + , "additionalProperties": false + , "required": [ "bytes" ] + , "properties": + { "bytes": { "$ref": "cardano.json#/definitions/Int64" } + } + } + + , "OperationalCertificate": + { "title": "OperationalCertificate" + , "type": "object" + , "description": "Certificate identifying a stake pool operator." + , "additionalProperties": false + , "required": [ "count", "kes" ] + , "properties": + { "count": { "$ref": "cardano.json#/definitions/UInt64" } + , "kes": + { "type": "object" + , "additionalProperties": false + , "required": [ "period", "verificationKey" ] + , "properties": + { "period": { "$ref": "cardano.json#/definitions/UInt64" } + , "verificationKey": { "$ref": "cardano.json#/definitions/KesVerificationKey" } + } + } + } + } + + , "Origin": + { "title": "Origin" + , "type": "string" + , "description": "The origin of the blockchain. This point is special in the sense that it doesn't point to any existing slots, but is preceding any existing other point." + , "enum": [ "origin" ] + } + + , "PolicyId": + { "title": "PolicyId" + , "$ref": "cardano.json#/definitions/Digest" + } + + , "StakePool": + { "title": "StakePool" + , "type": "object" + , "additionalProperties": false + , "required": + [ "id" + , "cost" + , "margin" + , "owners" + , "pledge" + , "relays" + , "rewardAccount" + , "vrfVerificationKeyHash" + ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/StakePoolId" + } + , "vrfVerificationKeyHash": + { "$ref": "cardano.json#/definitions/Digest" + } + , "owners": + { "type": "array" + , "items": + { "$ref": "cardano.json#/definitions/Digest" + } + } + , "cost": + { "$ref": "cardano.json#/definitions/Lovelace" + } + , "margin": + { "$ref": "cardano.json#/definitions/Ratio" + } + , "pledge": + { "$ref": "cardano.json#/definitions/Lovelace" + } + , "rewardAccount": + { "$ref": "cardano.json#/definitions/RewardAccount" + } + , "metadata": + { "type": "object" + , "title": "poolMetadata" + , "additionalProperties": false + , "required": ["hash","url"] + , "properties": + { "hash": { "$ref": "cardano.json#/definitions/Digest" } + , "url": + { "type": "string" + , "format": "uri" + } + } + } + , "relays": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Relay" } + } + } + } + + , "StakePoolId": + { "title": "StakePoolId" + , "type": "string" + , "description": "A Blake2b 32-byte hash digest of a pool's verification key." + , "contentEncoding": "bech32" + , "pattern": "^pool1[0-9a-z]*$" + , "examples": + [ "pool1qqqqpanw9zc0rzh0yp247nzf2s35uvnsm7aaesfl2nnejaev0uc" + , "pool1qqqqqdk4zhsjuxxd8jyvwncf5eucfskz0xjjj64fdmlgj735lr9" + ] + } + + , "ProposedProtocolParameters": + { "title": "ProposedProtocolParameters" + , "type": "object" + , "additionalProperties": false + , "properties": + { "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } + , "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "minUtxoDepositConstant": { "$ref": "cardano.json#/definitions/Lovelace" } + , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "extraEntropy": { "$ref": "cardano.json#/definitions/Nonce" } + , "stakeCredentialDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } + , "stakePoolDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } + , "stakePoolRetirementEpochBound": { "$ref": "cardano.json#/definitions/UInt64" } + , "stakePoolPledgeInfluence": { "$ref": "cardano.json#/definitions/Ratio" } + , "minStakePoolCost": { "$ref": "cardano.json#/definitions/Lovelace" } + , "desiredNumberOfStakePools": { "$ref": "cardano.json#/definitions/UInt64" } + , "federatedBlockProductionRatio": { "$ref": "cardano.json#/definitions/Ratio" } + , "monetaryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } + , "treasuryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } + , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } + , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } + , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } + , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } + , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } + } + } + + , "ProtocolParameters": + { "title": "ProtocolParameters" + , "type": "object" + , "additionalProperties": false + , "required": + [ "minFeeCoefficient" + , "minFeeConstant" + , "minUtxoDepositCoefficient" + , "minUtxoDepositConstant" + , "maxBlockBodySize" + , "maxBlockHeaderSize" + , "stakeCredentialDeposit" + , "stakePoolDeposit" + , "stakePoolRetirementEpochBound" + , "stakePoolPledgeInfluence" + , "minStakePoolCost" + , "monetaryExpansion" + , "treasuryExpansion" + , "desiredNumberOfStakePools" + , "version" + ] + , "properties": + { "minFeeCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "minFeeConstant": { "$ref": "cardano.json#/definitions/Lovelace" } + , "minUtxoDepositCoefficient": { "$ref": "cardano.json#/definitions/UInt64" } + , "minUtxoDepositConstant": { "$ref": "cardano.json#/definitions/Lovelace" } + , "maxBlockBodySize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxBlockHeaderSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxTransactionSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "maxValueSize": { "$ref": "cardano.json#/definitions/NumberOfBytes" } + , "extraEntropy": { "$ref": "cardano.json#/definitions/Nonce" } + , "stakeCredentialDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } + , "stakePoolDeposit": { "$ref": "cardano.json#/definitions/Lovelace" } + , "stakePoolRetirementEpochBound": { "$ref": "cardano.json#/definitions/UInt64" } + , "stakePoolPledgeInfluence": { "$ref": "cardano.json#/definitions/Ratio" } + , "minStakePoolCost": { "$ref": "cardano.json#/definitions/Lovelace" } + , "desiredNumberOfStakePools": { "$ref": "cardano.json#/definitions/UInt64" } + , "federatedBlockProductionRatio": { "$ref": "cardano.json#/definitions/Ratio" } + , "monetaryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } + , "treasuryExpansion": { "$ref": "cardano.json#/definitions/Ratio" } + , "collateralPercentage": { "$ref": "cardano.json#/definitions/UInt64" } + , "maxCollateralInputs": { "$ref": "cardano.json#/definitions/UInt64" } + , "plutusCostModels": { "$ref": "cardano.json#/definitions/CostModels" } + , "scriptExecutionPrices": { "$ref": "cardano.json#/definitions/ScriptExecutionPrices" } + , "maxExecutionUnitsPerTransaction": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "maxExecutionUnitsPerBlock": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + , "version": { "$ref": "cardano.json#/definitions/ProtocolVersion" } + } + } + + , "ProtocolVersion": + { "title": "ProtocolVersion" + , "type": "object" + , "additionalProperties": false + , "required": [ "major", "minor" ] + , "properties": + { "major": { "$ref": "cardano.json#/definitions/UInt32" } + , "minor": { "$ref": "cardano.json#/definitions/UInt32" } + , "patch": { "$ref": "cardano.json#/definitions/UInt32" } + } + } + + , "Ratio": + { "title": "Ratio" + , "type": "string" + , "description": "A ratio of two integers, to express exact fractions." + , "pattern": "^-?[0-9]+/[0-9]+$" + , "examples": + [ "2/3" + , "7/8" + ] + } + + , "Redeemer": + { "title": "Redeemer" + , "type": "object" + , "examples": + [ { "executionUnits": + { "memory": 2 + , "cpu": 2 + } + , "redeemer": "ggRCqSQ=" + } + ] + , "additionalProperties": false + , "required": [ "redeemer", "executionUnits" ] + , "properties": + { "redeemer": { "$ref": "cardano.json#/definitions/RedeemerData" } + , "executionUnits": { "$ref": "cardano.json#/definitions/ExecutionUnits" } + } + } + + , "RedeemerData": + { "title": "RedeemerData" + , "type": "string" + , "contentEncoding": "base16" + , "description": "Plutus data, CBOR-serialised." + } + + , "RedeemerPointer": + { "title": "RedeemerPointer" + , "type": "string" + , "pattern": "^(spend|mint|certificate|withdrawal):[0-9]+$" + } + + , "RelativeTime": + { "title": "RelativeTime" + , "type": "number" + , "description": "A time in seconds relative to another one (typically, system start or era start)." + } + + , "Relay": + { "title": "Relay" + , "oneOf": + [ { "type": "object" + , "title": "by address" + , "additionalProperties": false + , "required": [ "type" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "ipAddress" ] + } + , "ipv4": + { "type": "string" + } + , "ipv6": + { "type": "string" + } + , "port": + { "type": "integer" + , "minimum": 0 + , "maximum": 65535 + } + } + } + , { "type": "object" + , "title": "by name" + , "additionalProperties": false + , "required": [ "type", "hostname" ] + , "properties": + { "type": + { "type": "string" + , "enum": [ "hostname" ] + } + , "hostname": + { "type": "string" + } + , "port": + { "type": "integer" + , "minimum": 0 + , "maximum": 65535 + } + } + } + ] + } + + , "RewardAccount": + { "title": "RewardAccount" + , "type": "string" + , "description": "A reward account, also known as 'stake address'." + , "contentEncoding": "bech32" + , "pattern": "^stake(_test)?1[0-9a-z]+$" + , "examples": + [ "stake1ux7pt9adw8z46tgqn2f8fvurrhk325gcm4mf75mkmmxpx6gae9mzv" + ] + } + + , "RewardTransfer": + { "title": "RewardTransfer" + , "type": "object" + , "additionalProperties": { "$ref": "cardano.json#/definitions/LovelaceDelta" } + , "propertyNames": { "pattern": "[0-9a-f]{56}$" } + , "examples": + [ { "6d06fe0a5a8cb6d2bcc352581dea626bb5b2f66edf85678b2f2fa7b5": 123456789 + } + ] + } + + , "SafeZone": + { "title": "SafeZone" + , "type": "integer" + , "description": "Number of slots from the tip of the ledger in which it is guaranteed that no hard fork can take place. This should be (at least) the number of slots in which we are guaranteed to have k blocks." + , "minimum": 0 + , "maximum": 18446744073709552999 + } + + , "Script": + { "title": "Script" + , "oneOf": + [ { "type": "object" + , "title": "Native" + , "additionalProperties": false + , "required": [ "language", "cbor", "json" ] + , "properties": + { "language": + { "type": "string" + , "enum": [ "native" ] + } + , "json": + { "$ref": "cardano.json#/definitions/Script" + } + , "cbor": + { "type": "string" + , "contentEncoding": "base16" + } + } + } + , { "type": "object" + , "title": "Plutus" + , "additionalProperties": false + , "required": [ "language", "cbor" ] + , "properties": + { "language": + { "type": "string" + , "enum": [ "plutus:v1", "plutus:v2", "plutus:v3" ] + } + , "cbor": + { "type": "string" + , "contentEncoding": "base16" + } + } + } + ] + } + + , "Script": + { "title": "Script" + , "description": "A phase-1 monetary script. Timelocks constraints are only supported since Allegra." + , "examples": + [ { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } + , { "clause": "all" + , "from": + [ { "clause": "signature", "from": "ec09e5293d384637cd2f004356ef320f3fe3c07030e36bfffe67e2e2" } + , { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } + ] + } + , { "clause": "some" + , "atLeast": 2 + , "from": + [ { "clause": "signature", "from": "ec09e5293d384637cd2f004356ef320f3fe3c07030e36bfffe67e2e2" } + , { "clause": "signature", "from": "3c07030e36bfff7cd2f004356ef320f3fe3c07030e7cd2f004356437" } + , { "clause": "after", "slot": 42 } + ] + } + ] + , "oneOf": + [ { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "from" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "signature" ] + } + , "from": + { "$ref": "cardano.json#/definitions/Digest" + } + } + } + , { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "from" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "any" ] + } + , "from": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Script" } + } + } + } + + , { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "from" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "all" ] + } + , "from": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Script" } + } + } + } + , { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "from", "atLeast" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "some" ] + } + , "atLeast": + { "type": "integer" + } + , "from": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Script" } + } + } + } + , { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "slot" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "before" ] + } + , "slot": + { "$ref": "cardano.json#/definitions/Slot" + } + } + } + , { "type": "object" + , "title": "Clause" + , "additionalProperties": false + , "required": [ "clause", "slot" ] + , "properties": + { "clause": + { "type": "string" + , "enum": [ "after" ] + } + , "slot": + { "$ref": "cardano.json#/definitions/Slot" + } + } + } + ] + } + + , "ScriptExecutionPrices": + { "title": "ScriptExecutionPrices" + , "type": "object" + , "additionalProperties": false + , "required": [ "memory", "cpu" ] + , "properties": + { "memory": { "$ref": "cardano.json#/definitions/Ratio" } + , "cpu": { "$ref": "cardano.json#/definitions/Ratio" } + } + } + + , "ScriptPurpose": + { "title": "ScriptPurpose" + , "oneOf": + [ { "title": "spend" + , "type": "object" + , "additionalProperties": false + , "required": [ "purpose", "outputReference" ] + , "properties": + { "purpose": + { "type": "string" + , "enum": [ "spend" ] + } + , "outputReference": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } + } + } + , { "title": "mint" + , "type": "object" + , "additionalProperties": false + , "required": [ "purpose", "policy" ] + , "properties": + { "purpose": + { "type": "string" + , "enum": [ "mint" ] + } + , "policy": { "$ref": "cardano.json#/definitions/PolicyId" } + } + } + , { "title": "publish" + , "type": "object" + , "additionalProperties": false + , "required": [ "purpose", "certificate" ] + , "properties": + { "purpose": + { "type": "string" + , "enum": [ "publish" ] + } + , "certificate": { "$ref": "cardano.json#/definitions/Certificate" } + } + } + , { "title": "withdraw" + , "type": "object" + , "additionalProperties": false + , "required": [ "purpose", "rewardAccount" ] + , "properties": + { "purpose": + { "type": "string" + , "enum": [ "withdraw" ] + } + , "rewardAccount": { "$ref": "cardano.json#/definitions/RewardAccount" } + } + } + ] + } + + , "Signature": + { "title": "Signature" + , "type": "string" + , "description": "An EdDSA signature." + , "contentEncoding": "base16" + , "minLength": 128 + , "maxLength": 128 + } + + , "Signatory": + { "title": "Signatory" + , "type": "object" + , "additionalProperties": false + , "required": [ "signature", "key" ] + , "properties": + { "key": { "$ref": "cardano.json#/definitions/VerificationKey" } + , "signature": { "$ref": "cardano.json#/definitions/Signature" } + , "chainCode": { "$ref": "cardano.json#/definitions/ChainCode" } + , "addressAttributes": { "$ref": "cardano.json#/definitions/AddressAttributes" } + } + , "examples": + [ { "signature": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b4ffffffff" + , "key": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01" + , "addressAttributes": "cA==" + , "chainCode": "b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b450" + } + , { "signature": "deeb8f82f2af5836ebbc1b450b6dbf0b03c93afe5696f10d49e8a8304ebfac01deeb8f82f2af5836ebbc1b4ffffffff" + , "key": "0c02af01eaacc939b3d0d817f4eb57d323ea5686cb1fecb8de821df1296b84a7" + } + ] + } + + , "Slot": + { "title": "Slot" + , "description": "An absolute slot number." + , "type": "integer" + , "minimum": 0 + , "maximum": 18446744073709552000 + } + + , "SlotLength": + { "title": "SlotLength" + , "description": "A slot length, in seconds, possibly with decimals." + , "type": "object" + , "additionalProperties": false + , "required": [ "seconds" ] + , "properties": + { "seconds": + { "type": "number" + } + } + } + + , "SoftwareVersion": + { "title": "SoftwareVersion" + , "type": "object" + , "additionalProperties": false + , "required": [ "appName", "number" ] + , "properties": + { "appName": { "type": "string" } + , "number": { "$ref": "cardano.json#/definitions/UInt32" } + } + } + + , "StakeAddress": + { "title": "StakeAddress" + , "type": "string" + , "description": "A stake address (a.k.a reward account)" + , "contentEncoding": "bech32" + , "pattern": "^(stake|stake_test)1[0-9a-z]*$" + , "examples": + [ "stake179kzq4qulejydh045yzxwk4ksx780khkl4gdve9kzwd9vjcek9u8h" + ] + } + + , "Tip": + { "title": "tip" + , "type": "object" + , "additionalProperties": false + , "required": [ "slot", "id", "blockNo" ] + , "properties": + { "slot": { "$ref": "cardano.json#/definitions/Slot" } + , "id": { "$ref": "cardano.json#/definitions/Digest" } + , "blockNo": { "$ref": "cardano.json#/definitions/BlockHeight" } + } + } + + , "Transaction": + { "title": "Transaction" + , "type": "object" + , "additionalProperties": false + , "required": [ "id", "inputSource", "inputs", "outputs", "signatories", "cbor" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/Digest" + } + , "inputSource": + { "$ref": "cardano.json#/definitions/InputSource" + } + , "inputs": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } + } + , "references": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } + } + , "collaterals": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/TransactionOutputReference" } + } + , "totalCollateral": + { "$ref": "cardano.json#/definitions/Lovelace" + } + , "collateralReturn": + { "$ref": "cardano.json#/definitions/TransactionOutput" + } + , "outputs": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/TransactionOutput" } + } + , "certificates": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Certificate" } + } + , "withdrawals": + { "$ref": "cardano.json#/definitions/Withdrawals" + } + , "fee": + { "$ref": "cardano.json#/definitions/Lovelace" + } + , "validityInterval": + { "$ref": "cardano.json#/definitions/ValidityInterval" + } + , "mint": + { "$ref": "cardano.json#/definitions/Assets" + } + , "network": + { "$ref": "cardano.json#/definitions/Network" + } + , "scriptIntegrityHash": + { "$ref": "cardano.json#/definitions/Digest" + } + , "requiredExtraSignatories": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Digest" } + } + , "requiredExtraScripts": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Digest" } + } + , "governanceActions": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/GovernanceAction" } + } + , "metadata": + { "$ref": "cardano.json#/definitions/Metadata" + } + , "signatories": + { "type": "array" + , "items": { "$ref": "cardano.json#/definitions/Signatory" } + } + , "scripts": + { "type": "object" + , "propertyNames": { "contentEncoding": "base16", "pattern": "^[0-9a-f]+$" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Script" } + } + , "datums": + { "type": "object" + , "propertyNames": { "contentEncoding": "base16", "pattern": "^[0-9a-f]+$" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Datum" } + } + , "redeemers": + { "type": "object" + , "propertyNames": { "$ref": "cardano.json#/definitions/RedeemerPointer" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/Redeemer" } + } + , "cbor": + { "type": "string" + , "contentEncoding": "base16" + , "description": "The raw serialized (CBOR) transaction, as found on-chain." + } + } + } + + , "TransactionId": + { "title": "TransactionId" + , "description": "A Blake2b 32-byte hash digest of a transaction body" + , "type": "string" + , "contentEncoding": "base16" + , "minLength": 64 + , "maxLength": 64 + } + + , "TransactionOutput": + { "title": "TransactionOutput" + , "description": "A transaction output. Since Mary, 'value' always return a multi-asset value. Since Alonzo, 'datumHash' is always present (albeit sometimes 'null'). Since Babbage, 'datum' & 'script' are always present (albeit sometimes 'null')." + , "type": "object" + , "examples": + [ { "address": "addr_test1qz66ue36465w2qq40005h2hadad6pnjht8mu6sgplsfj74qdjnshguewlx4ww0eet26y2pal4xpav5prcydf28cvxtjqx46x7f" + , "value": + { "coins": 2 + , "assets": + { "3542acb3a64d80c29302260d62c3b87a742ad14abf855ebc6733081e": 42 + , "b5ae663aaea8e500157bdf4baafd6f5ba0ce5759f7cd4101fc132f54.706174617465": 1337 + } + } + , "datumHash": null + , "datum": null + , "script": null + } + ] + , "additionalProperties": false + , "required": [ "address", "value" ] + , "properties": + { "address": { "$ref": "cardano.json#/definitions/Address" } + , "value": { "$ref": "cardano.json#/definitions/Value" } + , "datumHash": { "$ref": "cardano.json#/definitions/Digest" } + , "datum": { "$ref": "cardano.json#/definitions/Datum" } + , "script": { "$ref": "cardano.json#/definitions/Script" } + } + } + + , "TransactionOutputReference": + { "title": "TransactionOutputReference" + , "type": "object" + , "additionalProperties": false + , "required": [ "transaction", "output" ] + , "properties": + { "transaction": + { "type": "object" + , "additionalProperties": false + , "required": [ "id" ] + , "properties": + { "id": + { "$ref": "cardano.json#/definitions/TransactionId" + } + } + } + , "output": + { "$ref": "cardano.json#/definitions/Index" + } + } + } + + , "UInt8": + { "title": "UInt8" + , "type": "integer" + , "minimum": 0 + , "maximum": 255 + } + + , "UInt32": + { "title": "UInt32" + , "type": "integer" + , "minimum": 0 + , "maximum": 4294967295 + } + + , "UInt64": + { "title": "UInt64" + , "type": "integer" + , "minimum": 0 + , "maximum": 18446744073709552999 + } + + , "UtcTime": + { "title": "UtcTime" + , "type": "string" + , "format": "date-time" + , "pattern": "[0-9]{4}-[0-9]{2}-[0-9]{2}T[0-9]{2}:[0-9]{2}:[0-9]{2}.?[0-9]*Z?" + } + + , "Utxo": + { "title": "Utxo" + , "type": "object" + , "propertyNames": + { "pattern": "^[0-9a-f]{64}#[0-9]+$" } + , "items": { "$ref": "cardano.json#/definitions/TransactionOutput" } + , "example": + { "09d34606abdcd0b10ebc89307cbfa0b469f9144194137b45b7a04b273961add8#687": + { "address": "addr1w9htvds89a78ex2uls5y969ttry9s3k9etww0staxzndwlgmzuul5" + , "value": + { "lovelace": 7620669 } + } + } + } + + , "ValidityInterval": + { "title": "ValidityInterval" + , "type": "object" + , "additionalProperties": false + , "properties": + { "invalidBefore": { "$ref": "cardano.json#/definitions/Slot" } + , "invalidAfter": { "$ref": "cardano.json#/definitions/Slot" } + } + } + + , "Value": + { "title": "Value" + , "type": "object" + , "propertyNames": { "pattern": "^[0-9a-z]{56}$" } + , "additionalProperties": + { "type": "object" + , "propertyNames": { "pattern": "^[0-9a-z]{0,64}$" } + , "additionalProperties": { "$ref": "cardano.json#/definitions/AssetQuantity" } + } + , "required": [ "ada" ] + , "properties": + { "ada": + { "type": "object" + , "additionalProperties": false + , "required": [ "lovelace" ] + , "properties": + { "lovelace": { "type": "integer" } + } + } + } + } + + , "VerificationKey": + { "title": "VerificationKey" + , "description": "An Ed25519 verification key." + , "type": "string" + , "contentEncoding": "base16" + , "minLength": 64 + , "maxLength": 64 + } + + , "VoterRole": + { "title": "VoterRole" + , "type": "string" + , "enum": [ "constitutionalCommittee", "delegateRepresentative", "stakePoolOperator" ] + } + + , "VotingPeriod": + { "title": "VotingPeriod" + , "type": "string" + , "enum": [ "voteForThisEpoch", "voteForNextEpoch" ] + } + + , "VrfProof": + { "title": "VrfProof" + , "type": "string" + , "contentEncoding": "base16" + } + + , "VrfOutput": + { "title": "VrfOutput" + , "type": "string" + , "contentEncoding": "base16" + } + + , "Withdrawals": + { "title": "Withdrawals" + , "type": "object" + , "additionalProperties": { "$ref": "cardano.json#/definitions/Lovelace" } + , "propertyNames": { "pattern": "^stake(_test)?1[0-9a-z]+$" } + } + } +} From c392a1d6eb48e319b737c276af9e62e1413bbcd3 Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 10:20:11 +0100 Subject: [PATCH 07/11] Add "our" ProtocolParameters JSON schema to api.yaml This is the one implemented by cardano-cli and the same format the hydra-node expects on the command line. --- hydra-node/json-schemas/api.yaml | 129 ++++++++++++++++++++++++- hydra-node/src/Hydra/API/HTTPServer.hs | 4 +- hydra-node/test/Hydra/JSONSchema.hs | 7 +- 3 files changed, 132 insertions(+), 8 deletions(-) diff --git a/hydra-node/json-schemas/api.yaml b/hydra-node/json-schemas/api.yaml index c900b705968..0137a73f0c4 100644 --- a/hydra-node/json-schemas/api.yaml +++ b/hydra-node/json-schemas/api.yaml @@ -849,9 +849,7 @@ components: ProtocolParameters: title: ProtocolParameters payload: - type: object - additionalProperties: false - $ref: "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/ProtocolParameters" + $ref: "api.yaml#/components/schemas/ProtocolParameters" IgnoredHeadInitializing: title: IgnoredHeadInitializing @@ -1056,6 +1054,129 @@ components: "port": 5001 } + # NOTE: We are not using the cardanonical/cardano.json#ProtocolParameters as + # we need to be compatible with what the cardano-cli provides us + ProtocolParameters: + description: | + Cardano protocol parameters as provided by the cardano-cli and accepted + by the hydra-node on the command line. + type: object + # Allow additional parameters to not be too strict about retired values + # like minUTxOValue + additionalProperties: true + required: + - protocolVersion + - maxBlockHeaderSize + - maxBlockBodySize + - maxTxSize + - txFeeFixed + - txFeePerByte + - stakeAddressDeposit + - stakePoolDeposit + - minPoolCost + - poolRetireMaxEpoch + - stakePoolTargetNum + - poolPledgeInfluence + - monetaryExpansion + - treasuryCut + - costModels # Alonzo onwards + - executionUnitPrices # Alonzo onwards + - maxTxExecutionUnits # Alonzo onwards + - maxBlockExecutionUnits # Alonzo onwards + - maxValueSize # Alonzo onwards + - collateralPercentage # Alonzo onwards + - maxCollateralInputs # Alonzo onwards + - utxoCostPerByte # Babbage onwards + properties: + protocolVersion: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/ProtocolVersion" + maxBlockBodySize: + # XXX: NumberOfBytes in cardanonical + type: integer + minimum: 0 + maxBlockHeaderSize: + # XXX: NumberOfBytes in cardanonical + type: integer + minimum: 0 + maxTxSize: + # XXX: NumberOfBytes in cardanonical + type: integer + minimum: 0 + txFeeFixed: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Lovelace" + txFeePerByte: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/UInt64" + stakeAddressDeposit: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Lovelace" + stakePoolDeposit: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Lovelace" + minPoolCost: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Lovelace" + poolRetireMaxEpoch: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/UInt64" + stakePoolTargetNum: + # XXX: UInt64 in cardanonical, but Natural in cardano-api + type: integer + minimum: 0 + poolPledgeInfluence: + # XXX: would be better "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Ratio" + type: number + monetaryExpansion: + # XXX: would be better "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Ratio" + type: number + treasuryCut: + # XXX: would be better "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Ratio" + type: number + costModels: + type: object + # XXX: Different key naming scheme than in cardanonical + propertyNames: + title: Language + type: string + enum: + - "PlutusV1" + - "PlutusV2" + - "PlutusV3" + additionalProperties: + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/CostModel" + executionUnitPrices: + # XXX: Object fields different in cardanonical and using Ratio + priceMemory: + type: number + priceSteps: + type: number + maxTxExecutionUnits: + # XXX: Object fields different in cardanonical + properties: + # XXX: UInt64 in cardanonical, but Rational in cardano-api + memory: + type: number + cpu: + type: number + maxBlockExecutionUnits: + # XXX: Object fields different in cardanonical + properties: + # XXX: UInt64 in cardanonical, but Rational in cardano-api + memory: + type: number + cpu: + type: number + maxValueSize: + # XXX: NumberOfBytes in cardanonical + type: integer + minimum: 0 + collateralPercentage: + # XXX: UInt64 in cardanonical, but Natural in cardano-api + type: integer + minimum: 0 + maxCollateralInputs: + # XXX: UInt64 in cardanonical, but Natural in cardano-api + type: integer + minimum: 0 + utxoCostPerByte: + # XXX: Coefficient in cardanonical is UInt64, but should be lovelace + "$ref": "https://raw.githubusercontent.com/CardanoSolutions/cardanonical/main/cardano.json#/definitions/Lovelace" + NodeId: type: string description: Hydra Node identifier @@ -1901,7 +2022,7 @@ components: type: object propertyNames: pattern: "^[0-9a-f]{64}#[0-9]+$" - items: + items: # REVIEW: does this work? use additionalProperties here? $ref: "api.yaml#/components/schemas/TxOut" example: { diff --git a/hydra-node/src/Hydra/API/HTTPServer.hs b/hydra-node/src/Hydra/API/HTTPServer.hs index ba0e2d1b547..b974f832a44 100644 --- a/hydra-node/src/Hydra/API/HTTPServer.hs +++ b/hydra-node/src/Hydra/API/HTTPServer.hs @@ -25,9 +25,11 @@ import Hydra.Cardano.Api ( TxOut, UTxO', deserialiseFromTextEnvelope, + fromLedgerPParams, mkScriptWitness, proxyToAsType, serialiseToTextEnvelope, + shelleyBasedEra, pattern KeyWitness, pattern ScriptWitness, ) @@ -166,7 +168,7 @@ httpApp tracer directChain pparams getInitializingHeadId request respond = do >>= handleDraftCommitUtxo directChain getInitializingHeadId >>= respond ("GET", ["protocol-parameters"]) -> - respond $ responseLBS status200 [] (Aeson.encode pparams) + respond $ responseLBS status200 [] (Aeson.encode $ fromLedgerPParams shelleyBasedEra pparams) ("POST", ["cardano-transaction"]) -> consumeRequestBodyStrict request >>= handleSubmitUserTx directChain diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/test/Hydra/JSONSchema.hs index 71e1712ff9f..c6ffe6d3f23 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/test/Hydra/JSONSchema.hs @@ -77,9 +77,9 @@ validateJSON schemaFilePath selector value = do when (exitCode /= ExitSuccess) $ failure . toString $ unlines - [ "check-jsonschema failed on " <> toText jsonInput <> " with schema " <> toText jsonSchema - , toText out - , toText err + [ "check-jsonschema failed on " <> toText jsonInput <> " with schema " <> toText jsonSchema <> " on input:" + , decodeUtf8 $ encodePretty value + , toText err <> toText out ] where copySchemasTo dir = do @@ -121,6 +121,7 @@ prop_validateJSONSchema specFileName selector = writeFileLBS jsonInput (Aeson.encode samples) writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) monitor $ counterexample (decodeUtf8 . Aeson.encode $ samples) + -- TODO: should be able to re-use validateJSON here (exitCode, out, err) <- run $ do readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] mempty monitor $ counterexample out From b10a7e741e101e39147855142deef85d77ce8f72 Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 10:23:48 +0100 Subject: [PATCH 08/11] Respond with correct JSON on /protocol-parameters This matches now what we also accept on the command line and what the cardano-cli is giving us. --- hydra-node/src/Hydra/API/HTTPServer.hs | 3 ++- hydra-node/test/Hydra/API/HTTPServerSpec.hs | 4 ++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/hydra-node/src/Hydra/API/HTTPServer.hs b/hydra-node/src/Hydra/API/HTTPServer.hs index b974f832a44..a28864ed9f7 100644 --- a/hydra-node/src/Hydra/API/HTTPServer.hs +++ b/hydra-node/src/Hydra/API/HTTPServer.hs @@ -168,7 +168,8 @@ httpApp tracer directChain pparams getInitializingHeadId request respond = do >>= handleDraftCommitUtxo directChain getInitializingHeadId >>= respond ("GET", ["protocol-parameters"]) -> - respond $ responseLBS status200 [] (Aeson.encode $ fromLedgerPParams shelleyBasedEra pparams) + respond . responseLBS status200 [] . Aeson.encode $ + fromLedgerPParams shelleyBasedEra pparams ("POST", ["cardano-transaction"]) -> consumeRequestBodyStrict request >>= handleSubmitUserTx directChain diff --git a/hydra-node/test/Hydra/API/HTTPServerSpec.hs b/hydra-node/test/Hydra/API/HTTPServerSpec.hs index 5b665969d61..7835e6d6588 100644 --- a/hydra-node/test/Hydra/API/HTTPServerSpec.hs +++ b/hydra-node/test/Hydra/API/HTTPServerSpec.hs @@ -9,7 +9,7 @@ import Data.Aeson.Lens (key, nth) import Data.ByteString.Base16 qualified as Base16 import Hydra.API.HTTPServer (DraftCommitTxRequest, DraftCommitTxResponse, SubmitTxRequest (..), TransactionSubmitted, httpApp) import Hydra.API.ServerSpec (dummyChainHandle) -import Hydra.Cardano.Api (serialiseToTextEnvelope, toLedgerTx) +import Hydra.Cardano.Api (fromLedgerPParams, serialiseToTextEnvelope, shelleyBasedEra, toLedgerTx) import Hydra.Chain.Direct.Fixture (defaultPParams) import Hydra.JSONSchema (SchemaSelector, prop_validateJSONSchema, validateJSON, withJsonSpecifications) import Hydra.Ledger.Cardano (Tx) @@ -102,7 +102,7 @@ apiServerSpec = do it "responds given parameters" $ get "/protocol-parameters" `shouldRespondWith` 200 - { matchBody = matchJSON defaultPParams + { matchBody = matchJSON $ fromLedgerPParams shelleyBasedEra defaultPParams } where webServer = httpApp nullTracer dummyChainHandle defaultPParams getHeadId From 7742a349065de206140a99adf79002076d66d0df Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 10:49:30 +0100 Subject: [PATCH 09/11] Move JSONSchema module to new hydra-node:testlib This allows us to re-use this functionality from hydra-cluster tests, while still using package-specific functionality from hydra-node (accessing schema files) and avoids moving this into the production code base. --- hydra-cluster/hydra-cluster.cabal | 4 +-- .../test/Test/Hydra/Cluster/CardanoCliSpec.hs | 11 +++++-- hydra-node/hydra-node.cabal | 29 +++++++++++++++---- .../{test => testlib}/Hydra/JSONSchema.hs | 3 +- 4 files changed, 35 insertions(+), 12 deletions(-) rename hydra-node/{test => testlib}/Hydra/JSONSchema.hs (99%) diff --git a/hydra-cluster/hydra-cluster.cabal b/hydra-cluster/hydra-cluster.cabal index 86dd597c8f0..087b6f84763 100644 --- a/hydra-cluster/hydra-cluster.cabal +++ b/hydra-cluster/hydra-cluster.cabal @@ -160,7 +160,7 @@ test-suite tests build-depends: , aeson , async - , base >=4.7 && <5 + , base >=4.7 && <5 , bytestring , containers , directory @@ -168,7 +168,7 @@ test-suite tests , hspec , hydra-cardano-api , hydra-cluster - , hydra-node + , hydra-node:{hydra-node, testlib} , hydra-prelude , hydra-test-utils , io-classes diff --git a/hydra-cluster/test/Test/Hydra/Cluster/CardanoCliSpec.hs b/hydra-cluster/test/Test/Hydra/Cluster/CardanoCliSpec.hs index 61bdbb17f35..d74ff6e76d9 100644 --- a/hydra-cluster/test/Test/Hydra/Cluster/CardanoCliSpec.hs +++ b/hydra-cluster/test/Test/Hydra/Cluster/CardanoCliSpec.hs @@ -11,6 +11,7 @@ import Data.Aeson.Lens (key, _String) import Data.Aeson.Types (parseEither) import Hydra.API.HTTPServer (DraftCommitTxResponse (DraftCommitTxResponse)) import Hydra.Cardano.Api (Tx) +import Hydra.JSONSchema (validateJSON, withJsonSpecifications) import Hydra.Ledger.Cardano.Configuration (pparamsFromJson) import Hydra.Logging (showLogsOnFailure) import System.Exit (ExitCode (..)) @@ -46,8 +47,14 @@ spec = Left e -> failure $ "Failed to decode JSON: " <> e <> "\n" <> show protocolParameters Right _ -> pure () - it "query protocol-parameters matches our schema" $ \_tracer -> - pendingWith "TODO" + it "query protocol-parameters matches our schema" $ \tracer -> + withJsonSpecifications $ \tmpDir -> + withCardanoNodeDevnet tracer tmpDir $ \RunningNode{nodeSocket, networkId} -> do + pparamsValue <- cliQueryProtocolParameters nodeSocket (networkId) + validateJSON + (tmpDir "api.json") + (key "components" . key "schemas" . key "ProtocolParameters") + pparamsValue where cardanoCliSign txFile = proc diff --git a/hydra-node/hydra-node.cabal b/hydra-node/hydra-node.cabal index e5cb1f12148..6e852db9a6d 100644 --- a/hydra-node/hydra-node.cabal +++ b/hydra-node/hydra-node.cabal @@ -176,6 +176,28 @@ library ghc-options: -haddock +library testlib + import: project-config + visibility: public + hs-source-dirs: testlib + exposed-modules: Hydra.JSONSchema + other-modules: Paths_hydra_node + build-depends: + , aeson + , base + , containers + , directory + , filepath + , hydra-prelude + , hydra-test-utils + , lens + , lens-aeson + , process + , QuickCheck + , text + , versions + , yaml + executable hydra-node import: project-config hs-source-dirs: exe/hydra-node @@ -274,7 +296,6 @@ test-suite tests Hydra.FireForgetSpec Hydra.HeadLogicSnapshotSpec Hydra.HeadLogicSpec - Hydra.JSONSchema Hydra.JSONSchemaSpec Hydra.Ledger.Cardano.TimeSpec Hydra.Ledger.CardanoSpec @@ -331,7 +352,7 @@ test-suite tests , hspec-wai , HUnit , hydra-cardano-api - , hydra-node + , hydra-node:{hydra-node, testlib} , hydra-plutus , hydra-plutus-extras , hydra-prelude @@ -342,7 +363,6 @@ test-suite tests , lens-aeson , plutus-ledger-api:{plutus-ledger-api, plutus-ledger-api-testlib} >=1.1.1.0 , plutus-tx - , process , QuickCheck , quickcheck-dynamic >=3.3.1 && <3.4 , quickcheck-instances @@ -354,10 +374,7 @@ test-suite tests , time , typed-protocols-examples >=0.1.0.0 , vector - , versions - , wai-extra , websockets - , yaml build-tool-depends: hspec-discover:hspec-discover ghc-options: -threaded -rtsopts diff --git a/hydra-node/test/Hydra/JSONSchema.hs b/hydra-node/testlib/Hydra/JSONSchema.hs similarity index 99% rename from hydra-node/test/Hydra/JSONSchema.hs rename to hydra-node/testlib/Hydra/JSONSchema.hs index c6ffe6d3f23..bde2904cf3b 100644 --- a/hydra-node/test/Hydra/JSONSchema.hs +++ b/hydra-node/testlib/Hydra/JSONSchema.hs @@ -77,8 +77,7 @@ validateJSON schemaFilePath selector value = do when (exitCode /= ExitSuccess) $ failure . toString $ unlines - [ "check-jsonschema failed on " <> toText jsonInput <> " with schema " <> toText jsonSchema <> " on input:" - , decodeUtf8 $ encodePretty value + [ "check-jsonschema failed on " <> toText jsonInput <> " with schema " <> toText jsonSchema , toText err <> toText out ] where From 1921504312ffbdd4aeb7262fb9c39a98107bcc1f Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 15:48:07 +0100 Subject: [PATCH 10/11] Add check-jsonschema to hydra-cluster tests This test suite is now also running check-jsonschema and hence needs this binary available. --- nix/hydra/packages.nix | 1 + 1 file changed, 1 insertion(+) diff --git a/nix/hydra/packages.nix b/nix/hydra/packages.nix index b056508a2bf..f16a5c8e02d 100644 --- a/nix/hydra/packages.nix +++ b/nix/hydra/packages.nix @@ -135,6 +135,7 @@ rec { cardano-node.packages.${system}.cardano-node cardano-node.packages.${system}.cardano-cli hydra-chain-observer + pkgs.check-jsonschema ]; }; hydra-tui = pkgs.mkShellNoCC { From 9c13146220a7115c10004b431026ee12e007a97f Mon Sep 17 00:00:00 2001 From: Sebastian Nagel Date: Tue, 9 Jan 2024 16:02:16 +0100 Subject: [PATCH 11/11] Reuse validateJSONSchema in prop_validateJSONSchema --- hydra-node/test/Hydra/JSONSchemaSpec.hs | 11 +++++-- hydra-node/testlib/Hydra/JSONSchema.hs | 38 +++++++++++-------------- 2 files changed, 25 insertions(+), 24 deletions(-) diff --git a/hydra-node/test/Hydra/JSONSchemaSpec.hs b/hydra-node/test/Hydra/JSONSchemaSpec.hs index 523415bab7e..48456e9a409 100644 --- a/hydra-node/test/Hydra/JSONSchemaSpec.hs +++ b/hydra-node/test/Hydra/JSONSchemaSpec.hs @@ -7,11 +7,12 @@ import Test.Hydra.Prelude import Control.Exception (IOException) import Data.Aeson (Value (..), object, (.=)) import Data.Aeson.Lens (key) -import Hydra.JSONSchema (validateJSON, withJsonSpecifications) +import Hydra.JSONSchema (prop_validateJSONSchema, validateJSON, withJsonSpecifications) import System.FilePath (()) +import Test.QuickCheck.Instances.Time () spec :: Spec -spec = +spec = do describe "validateJSON withJsonSpecifications" $ do it "works using identity selector and Null input" $ withJsonSpecifications $ \dir -> @@ -49,3 +50,9 @@ spec = -- NOTE: MultiSignature has a local ref into api.yaml for Signature (key "components" . key "schemas" . key "MultiSignature") (object ["multiSignature" .= [String "bar"]]) + + describe "prop_validateJSONSchema" $ + it "works with api.yaml and UTCTime" $ + prop_validateJSONSchema @UTCTime + "api.yaml" + (key "components" . key "schemas" . key "UTCTime") diff --git a/hydra-node/testlib/Hydra/JSONSchema.hs b/hydra-node/testlib/Hydra/JSONSchema.hs index bde2904cf3b..a4107be9d34 100644 --- a/hydra-node/testlib/Hydra/JSONSchema.hs +++ b/hydra-node/testlib/Hydra/JSONSchema.hs @@ -23,7 +23,7 @@ import System.Exit (ExitCode (..)) import System.FilePath (normalise, takeBaseName, takeDirectory, takeExtension, takeFileName, (<.>), ()) import System.IO.Error (IOError, isDoesNotExistError) import System.Process (readProcessWithExitCode) -import Test.QuickCheck (Property, counterexample, forAllShrink, resize, vectorOf) +import Test.QuickCheck (Property, counterexample, forAllShrink, mapSize, vectorOf, withMaxSuccess) import Test.QuickCheck.Monadic (assert, monadicIO, monitor, run) import Prelude qualified @@ -100,32 +100,26 @@ prop_validateJSONSchema :: SchemaSelector -> Property prop_validateJSONSchema specFileName selector = - forAllShrink (resize 10 arbitrary) shrink $ \(samples :: [a]) -> - monadicIO $ do - withJsonSpecifications $ \tmpDir -> do - run ensureSystemRequirements - let jsonInput = tmpDir "jsonInput" - let jsonSchema = tmpDir "jsonSchema" - let specJsonFile = tmpDir specFileName - mSpecs <- run $ Aeson.decodeFileStrict specJsonFile - case mSpecs of - Nothing -> error "Failed to decode specFile to JSON" - Just specs -> run $ do - let jsonSpecSchema = + -- NOTE: Avoid slow execution (due to external program) by testing the + -- property once with size 100 instead of 100 times with growing sizes. + withMaxSuccess 1 . mapSize (const 100) $ + forAllShrink arbitrary shrink $ \(samples :: [a]) -> + monadicIO $ do + withJsonSpecifications $ \tmpDir -> do + run ensureSystemRequirements + let jsonSchema = tmpDir "jsonSchema" + run $ + Aeson.decodeFileStrict (tmpDir specFileName) >>= \case + Nothing -> error "Failed to decode specFile to JSON" + Just specs -> do + Aeson.encodeFile jsonSchema $ Aeson.object [ "$id" .= ("file://" <> tmpDir <> "/") , "type" .= Aeson.String "array" , "items" .= (specs ^? selector) ] - writeFileLBS jsonInput (Aeson.encode samples) - writeFileLBS jsonSchema (Aeson.encode jsonSpecSchema) - monitor $ counterexample (decodeUtf8 . Aeson.encode $ samples) - -- TODO: should be able to re-use validateJSON here - (exitCode, out, err) <- run $ do - readProcessWithExitCode "check-jsonschema" ["--schemafile", jsonSchema, jsonInput] mempty - monitor $ counterexample out - monitor $ counterexample err - assert (exitCode == ExitSuccess) + monitor $ counterexample (decodeUtf8 . Aeson.encode $ samples) + run $ validateJSON jsonSchema id (toJSON samples) -- | Check specification is complete wr.t. to generated data -- This second sub-property ensures that any key found in the