{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Cardano.Ledger.Babbage.HuddleSpec (
  module Cardano.Ledger.Alonzo.HuddleSpec,
  babbageCDDL,
  babbageOperationalCertRule,
  babbageProtocolVersionRule,
  babbageTransactionOutput,
  babbageScript,
) where

import Cardano.Ledger.Alonzo.HuddleSpec hiding (
  shelleyOperationalCertGroup,
  shelleyProtocolVersionGroup,
 )
import Cardano.Ledger.Babbage (BabbageEra)
import Codec.CBOR.Cuddle.Comments ((//-))
import Codec.CBOR.Cuddle.Huddle
import Data.Proxy (Proxy (..))
import Data.Word (Word64)
import Text.Heredoc
import Prelude hiding ((/))

babbageCDDL :: Huddle
babbageCDDL :: Huddle
babbageCDDL =
  [HuddleItem] -> Huddle
collectFrom
    [ Rule -> HuddleItem
HIRule (Rule -> HuddleItem) -> Rule -> HuddleItem
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"block" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BabbageEra)
    , Rule -> HuddleItem
HIRule (Rule -> HuddleItem) -> Rule -> HuddleItem
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BabbageEra)
    , Rule -> HuddleItem
HIRule (Rule -> HuddleItem) -> Rule -> HuddleItem
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"kes_signature" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BabbageEra)
    , Rule -> HuddleItem
HIRule (Rule -> HuddleItem) -> Rule -> HuddleItem
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"language" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BabbageEra)
    , Rule -> HuddleItem
HIRule (Rule -> HuddleItem) -> Rule -> HuddleItem
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"signkey_kes" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BabbageEra)
    ]

-- | Babbage changed protocol_version from Named Group to Rule to match actual block
-- serialization. See 'header_body' instance for full explanation.
-- Ref: PR #3762, Issue #3559
babbageProtocolVersionRule ::
  forall era. HuddleRule "major_protocol_version" era => Proxy era -> Rule
babbageProtocolVersionRule :: forall era.
HuddleRule "major_protocol_version" era =>
Proxy era -> Rule
babbageProtocolVersionRule Proxy era
p =
  Text
"protocol_version" Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"major_protocol_version" Proxy era
p, Value Int -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a Value Int
VUInt]

-- | Babbage changed operational_cert from Named Group to Rule to match actual block
-- serialization. See 'header_body' instance for full explanation.
-- Ref: PR #3762, Issue #3559
babbageOperationalCertRule :: forall era. Era era => Proxy era -> Rule
babbageOperationalCertRule :: forall era. Era era => Proxy era -> Rule
babbageOperationalCertRule Proxy era
p =
  Text
"operational_cert"
    Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
      [ Key
"hot_vkey" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"kes_vkey" Proxy era
p
      , Key
"sequence_number" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"sequence_number" Proxy era
p
      , Key
"kes_period" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"kes_period" Proxy era
p
      , Key
"sigma" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"signature" Proxy era
p
      ]

instance HuddleGroup "account_registration_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
accountRegistrationCertGroup @BabbageEra

instance HuddleGroup "account_unregistration_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
accountUnregistrationCertGroup @BabbageEra

instance HuddleGroup "delegation_to_stake_pool_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
delegationToStakePoolCertGroup @BabbageEra

instance HuddleGroup "pool_registration_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
HuddleGroup "pool_params" era =>
Proxy era -> Named Group
poolRegistrationCertGroup @BabbageEra

instance HuddleGroup "pool_retirement_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
poolRetirementCertGroup @BabbageEra

instance HuddleGroup "genesis_delegation_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
(HuddleRule "genesis_hash" era,
 HuddleRule "genesis_delegate_hash" era) =>
Proxy era -> Named Group
genesisDelegationCertGroup @BabbageEra

instance HuddleGroup "move_instantaneous_rewards_cert" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
HuddleRule "move_instantaneous_reward" era =>
Proxy era -> Named Group
moveInstantaneousRewardsCertGroup @BabbageEra

instance HuddleRule "certificate" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
(HuddleGroup "account_registration_cert" era,
 HuddleGroup "account_unregistration_cert" era,
 HuddleGroup "delegation_to_stake_pool_cert" era,
 HuddleGroup "pool_registration_cert" era,
 HuddleGroup "pool_retirement_cert" era,
 HuddleGroup "genesis_delegation_cert" era,
 HuddleGroup "move_instantaneous_rewards_cert" era) =>
Proxy era -> Rule
certificateRule @BabbageEra

instance HuddleRule "withdrawals" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
withdrawalsRule @BabbageEra

instance HuddleRule "genesis_hash" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
genesisHashRule @BabbageEra

instance HuddleRule "genesis_delegate_hash" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
genesisDelegateHashRule @BabbageEra

instance HuddleGroup "pool_params" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
(HuddleRule "relay" era, HuddleRule "pool_metadata" era) =>
Proxy era -> Named Group
poolParamsGroup @BabbageEra

instance HuddleRule "pool_metadata" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. HuddleRule "url" era => Proxy era -> Rule
poolMetadataRule @BabbageEra

instance HuddleRule "dns_name" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
dnsNameRule

instance HuddleRule "url" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
urlRule

instance HuddleGroup "single_host_addr" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
singleHostAddrGroup @BabbageEra

instance HuddleGroup "single_host_name" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. HuddleRule "dns_name" era => Proxy era -> Named Group
singleHostNameGroup @BabbageEra

instance HuddleGroup "multi_host_name" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. HuddleRule "dns_name" era => Proxy era -> Named Group
multiHostNameGroup @BabbageEra

instance HuddleRule "relay" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
(HuddleGroup "single_host_addr" era,
 HuddleGroup "single_host_name" era,
 HuddleGroup "multi_host_name" era) =>
Proxy era -> Rule
relayRule @BabbageEra

instance HuddleRule "move_instantaneous_reward" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. HuddleRule "delta_coin" era => Proxy era -> Rule
moveInstantaneousRewardRule @BabbageEra

instance HuddleRule "delta_coin" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
deltaCoinRule

instance HuddleRule "transaction_id" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
transactionIdRule @BabbageEra

instance HuddleRule "transaction_input" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. HuddleRule "transaction_id" era => Proxy era -> Rule
transactionInputRule @BabbageEra

instance HuddleRule "vkeywitness" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
vkeywitnessRule @BabbageEra

instance HuddleRule "bootstrap_witness" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
bootstrapWitnessRule @BabbageEra

instance HuddleRule "int64" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
(HuddleRule "min_int64" era, HuddleRule "max_int64" era) =>
Proxy era -> Rule
int64Rule @BabbageEra

instance HuddleRule "min_int64" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
minInt64Rule

instance HuddleRule "max_int64" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
maxInt64Rule

instance HuddleRule "policy_id" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p = Text
"policy_id" Text -> Rule -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"script_hash" Proxy BabbageEra
p

instance HuddleRule "asset_name" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Text
"asset_name" Text -> Constrained -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Value ByteString
VBytes Value ByteString -> (Word64, Word64) -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
0 :: Word64, Word64
32 :: Word64)

instance HuddleRule "value" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"value"
      Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p
      Rule -> Seal Array -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> Seal Array
sarr [Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p, GRuleCall -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (GRuleCall -> Item ArrayChoice) -> GRuleCall -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ Proxy BabbageEra -> Value Int -> GRuleCall
forall era a.
(HuddleRule "policy_id" era, HuddleRule "asset_name" era,
 IsType0 a) =>
Proxy era -> a -> GRuleCall
multiasset Proxy BabbageEra
p Value Int
VUInt]

instance HuddleRule "mint" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p = Text
"mint" Text -> GRuleCall -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Proxy BabbageEra -> Rule -> GRuleCall
forall era a.
(HuddleRule "policy_id" era, HuddleRule "asset_name" era,
 IsType0 a) =>
Proxy era -> a -> GRuleCall
multiasset Proxy BabbageEra
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"int64" Proxy BabbageEra
p)

instance HuddleRule "proposed_protocol_parameter_updates" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
(HuddleRule "genesis_hash" era,
 HuddleRule "protocol_param_update" era) =>
Proxy era -> Rule
proposedProtocolParameterUpdatesRule @BabbageEra

instance HuddleRule "update" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
HuddleRule "proposed_protocol_parameter_updates" era =>
Proxy era -> Rule
updateRule @BabbageEra

instance HuddleRule "required_signers" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p = Text
"required_signers" Text -> GRuleCall -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
untaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"addr_keyhash" Proxy BabbageEra
p)

instance HuddleRule "network_id" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
networkIdRule

instance HuddleRule "bounded_bytes" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
boundedBytesRule

instance HuddleRule "big_uint" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigUintRule

instance HuddleRule "big_nint" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigNintRule

instance HuddleRule "big_int" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigIntRule

instance HuddleRule "distinct_bytes" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
distinctBytesRule

instance HuddleRule "plutus_v1_script" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era. HuddleRule "distinct_bytes" era => Proxy era -> Rule
plutusV1ScriptRule

instance HuddleRule "redeemers" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p = Text
"redeemers" Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"redeemer" Proxy BabbageEra
p)]

instance HuddleRule "redeemer" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|NEW
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"redeemer"
        Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
          [ Key
"tag" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"redeemer_tag" Proxy BabbageEra
p
          , Key
"index" Key -> Value Int -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt
          , Key
"data" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_data" Proxy BabbageEra
p
          , Key
"ex_units" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"ex_units" Proxy BabbageEra
p
          ]

instance HuddleRule "redeemer_tag" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|0: spend
          |1: mint
          |2: cert
          |3: reward
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"redeemer_tag" Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Integer -> Literal
int Integer
0 Literal -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Integer -> Literal
int Integer
1 Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Integer -> Literal
int Integer
2 Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Integer -> Literal
int Integer
3

instance HuddleRule "ex_units" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ = Rule
exUnitsRule

instance HuddleRule "ex_unit_prices" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"ex_unit_prices"
      Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
        [ Key
"mem_price" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_interval" Proxy BabbageEra
p
        , Key
"step_price" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_interval" Proxy BabbageEra
p
        ]

instance HuddleRule "positive_interval" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era. Era era => Proxy era -> Rule
positiveIntervalRule

instance HuddleRule "operational_cert" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
babbageOperationalCertRule @BabbageEra

instance HuddleRule "protocol_version" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
HuddleRule "major_protocol_version" era =>
Proxy era -> Rule
babbageProtocolVersionRule @BabbageEra

instance HuddleRule "major_protocol_version" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
majorProtocolVersionRule @BabbageEra

instance HuddleRule "block" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|Valid blocks must also satisfy the following two constraints:
          |  1) the length of transaction_bodies and transaction_witness_sets must be
          |     the same
          |  2) every transaction_index must be strictly smaller than the length of
          |     transaction_bodies
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"block"
        Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
          [ Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"header" Proxy BabbageEra
p
          , Key
"transaction_bodies" Key -> ArrayChoice -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_body" Proxy BabbageEra
p)]
          , Key
"transaction_witness_sets" Key -> ArrayChoice -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_witness_set" Proxy BabbageEra
p)]
          , Key
"auxiliary_data_set"
              Key -> MapChoice -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> MapChoice -> MapChoice
mp
                [ Word64
0
                    Word64 -> MapEntry -> MapEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> Key
forall r. IsType0 r => r -> Key
asKey (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_index" Proxy BabbageEra
p)
                    Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"auxiliary_data" Proxy BabbageEra
p
                ]
          , Key
"invalid_transactions" Key -> ArrayChoice -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_index" Proxy BabbageEra
p)]
          ]

instance HuddleRule "header" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"header"
      Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
        [ Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"header_body" Proxy BabbageEra
p
        , Key
"body_signature" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"kes_signature" Proxy BabbageEra
p
        ]

-- IMPORTANT: Babbage changed operational_cert and protocol_version from Named Group
-- (grp) to Rule (arr) to match actual block serialization.
--
-- Semantic difference:
--   * Named Group (grp): Fields are inlined directly into parent array.
--     -> header_body becomes a 14-element flat array
--   * Rule (arr): Fields are nested as separate sub-arrays.
--     -> header_body becomes a 10-element array with nested structures
--
-- Pre-Babbage eras (Shelley through Alonzo) used Named Group, but actual Babbage+
-- blocks serialize with Rule (nested arrays). This change corrects the CDDL spec to
-- match the actual CBOR serialization.
--
-- See 'babbageProtocolVersionRule' and 'operational_cert' instance for details.
-- References: PR #3762, Issue #3559
instance HuddleRule "header_body" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"header_body"
      Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
        [ Key
"block_number" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"block_number" Proxy BabbageEra
p
        , Key
"slot" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"slot" Proxy BabbageEra
p
        , Key
"prev_hash" Key -> Choice Type2 -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"hash32" Proxy BabbageEra
p Rule -> Value Void -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Value Void
VNil)
        , Key
"issuer_vkey" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"vkey" Proxy BabbageEra
p
        , Key
"vrf_vkey" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"vrf_vkey" Proxy BabbageEra
p
        , Key
"vrf_result" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"vrf_cert" Proxy BabbageEra
p ArrayEntry -> Comment -> ArrayEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"replaces nonce_vrf and leader_vrf"
        , Key
"block_body_size" Key -> Value Int -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt
        , Key
"block_body_hash" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"hash32" Proxy BabbageEra
p ArrayEntry -> Comment -> ArrayEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"merkle triple root"
        , Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"operational_cert" Proxy BabbageEra
p
        , Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"protocol_version" Proxy BabbageEra
p
        ]

instance HuddleRule "transaction" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"transaction"
      Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
        [ Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_body" Proxy BabbageEra
p
        , Rule -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Rule -> Item ArrayChoice) -> Rule -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_witness_set" Proxy BabbageEra
p
        , Value Bool -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a Value Bool
VBool
        , Choice Type2 -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"auxiliary_data" Proxy BabbageEra
p Rule -> Value Void -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Value Void
VNil)
        ]

instance HuddleRule "transaction_body" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"transaction_body"
      Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
        [ Word64 -> Key
idx Word64
0 Key -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
untaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy BabbageEra
p)
        , Word64 -> Key
idx Word64
1 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_output" Proxy BabbageEra
p)]
        , Word64 -> Key
idx Word64
2 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"fee"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
3 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"slot" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"time to live"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
4 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"certificate" Proxy BabbageEra
p)])
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
5 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"withdrawals" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
6 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"update" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
7 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"auxiliary_data_hash" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
8 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"slot" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"validity interval start"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
9 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"mint" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
11 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"script_data_hash" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
13 Key -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
untaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy BabbageEra
p)) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"collateral"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
14 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"required_signers" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
15 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"network_id" Proxy BabbageEra
p)
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
16 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_output" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"collateral return"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
17 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"total collateral"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
18 Key -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
untaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy BabbageEra
p)) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"reference inputs"
        ]

instance HuddleRule "script_data_hash" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|This is a hash of data which may affect evaluation of a script.
          |This data consists of:
          |  - The redeemers from the transaction_witness_set (the value of field 5).
          |  - The datums from the transaction_witness_set (the value of field 4).
          |  - The value in the costmdls map corresponding to the script's language
          |    (in field 18 of protocol_param_update.)
          |(In the future it may contain additional protocol parameters.)
          |
          |Since this data does not exist in contiguous form inside a transaction, it needs
          |to be independently constructed by each recipient.
          |
          |The bytestring which is hashed is the concatenation of three things:
          |  redeemers || datums || language views
          |The redeemers are exactly the data present in the transaction witness set.
          |Similarly for the datums, if present. If no datums are provided, the middle
          |field is omitted (i.e. it is the empty/null bytestring).
          |
          |language views CDDL:
          |{ * language => script_integrity_data }
          |
          |This must be encoded canonically, using the same scheme as in
          |RFC7049 section 3.9:
          | - Maps, strings, and bytestrings must use a definite-length encoding
          | - Integers must be as small as possible.
          | - The expressions for map length, string length, and bytestring length
          |   must be as short as possible.
          | - The keys in the map must be sorted as follows:
          |    -  If two keys have different lengths, the shorter one sorts earlier.
          |    -  If two keys have the same length, the one with the lower value
          |       in (byte-wise) lexical order sorts earlier.
          |
          |For PlutusV1 (language id 0), the language view is the following:
          |  - the value of costmdls map at key 0 (in other words, the script_integrity_data)
          |    is encoded as an indefinite length list and the result is encoded as a bytestring.
          |    (our apologies)
          |    For example, the script_integrity_data corresponding to the all zero costmodel for V1
          |    would be encoded as (in hex):
          |    58a89f00000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000ff
          |  - the language ID tag is also encoded twice. first as a uint then as
          |    a bytestring. (our apologies)
          |    Concretely, this means that the language version for V1 is encoded as
          |    4100 in hex.
          |For PlutusV2 (language id 1), the language view is the following:
          |  - the value of costmdls map at key 1 is encoded as an definite length list.
          |    For example, the script_integrity_data corresponding to the all zero costmodel for V2
          |    would be encoded as (in hex):
          |    98af0000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000
          |  - the language ID tag is encoded as expected.
          |    Concretely, this means that the language version for V2 is encoded as
          |    01 in hex.
          |
          |Note that each Plutus language represented inside a transaction must have
          |a cost model in the costmdls protocol parameter in order to execute,
          |regardless of what the script integrity data is.
          |
          |Finally, note that in the case that a transaction includes datums but does not
          |include the redeemers field, the script data format becomes (in hex):
          |[ 80 | datums | A0 ]
          |corresponding to a CBOR empty list and an empty map.
          |Note that a transaction might include the redeemers field and set it to the
          |empty map, in which case the user supplied encoding of the empty map is used.
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy BabbageEra -> Rule
forall era. Era era => Proxy era -> Rule
scriptDataHashRule Proxy BabbageEra
p

instance HuddleRule "transaction_output" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|Both of the Alonzo and Babbage style TxOut formats are equally valid
          |and can be used interchangeably.
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"transaction_output"
        Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"shelley_transaction_output" Proxy BabbageEra
p
        Rule -> Rule -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Proxy BabbageEra -> Rule -> Rule
forall era.
(HuddleRule "address" era, HuddleRule "value" era,
 HuddleRule "datum_option" era) =>
Proxy era -> Rule -> Rule
babbageTransactionOutput Proxy BabbageEra
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"script" Proxy BabbageEra
p)

instance HuddleRule "shelley_transaction_output" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"shelley_transaction_output"
      Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
        [ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"address" Proxy BabbageEra
p)
        , Key
"amount" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"value" Proxy BabbageEra
p
        , ArrayEntry -> ArrayEntry
forall a. CanQuantify a => a -> a
opt (Key
"datum_hash" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"hash32" Proxy BabbageEra
p)
        ]

babbageTransactionOutput ::
  forall era.
  (HuddleRule "address" era, HuddleRule "value" era, HuddleRule "datum_option" era) =>
  Proxy era -> Rule -> Rule
babbageTransactionOutput :: forall era.
(HuddleRule "address" era, HuddleRule "value" era,
 HuddleRule "datum_option" era) =>
Proxy era -> Rule -> Rule
babbageTransactionOutput Proxy era
p Rule
script =
  Text
"babbage_transaction_output"
    Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
      [ Word64 -> Key
idx Word64
0 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"address" Proxy era
p
      , Word64 -> Key
idx Word64
1 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"value" Proxy era
p
      , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
2 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"datum_option" Proxy era
p MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
      , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
3 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> (Text
"script_ref" Text -> Tagged Constrained -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Word64 -> Constrained -> Tagged Constrained
forall a. Word64 -> a -> Tagged a
tag Word64
24 (Value ByteString
VBytes Value ByteString -> Rule -> Constrained
forall b c.
(IsCborable b, IsConstrainable c b) =>
c -> Rule -> Constrained
`cbor` Rule
script)) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
      ]

instance HuddleRule "datum_option" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"datum_option"
      Text -> Array -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
0, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"hash32" Proxy BabbageEra
p)]
      ArrayChoice -> ArrayChoice -> Array
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
1, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"data" Proxy BabbageEra
p)]

instance HuddleRule "data" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"data" Text -> Tagged Constrained -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Word64 -> Constrained -> Tagged Constrained
forall a. Word64 -> a -> Tagged a
tag Word64
24 (Value ByteString
VBytes Value ByteString -> Rule -> Constrained
forall b c.
(IsCborable b, IsConstrainable c b) =>
c -> Rule -> Constrained
`cbor` forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_data" Proxy BabbageEra
p)

instance HuddleRule "transaction_witness_set" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"transaction_witness_set"
      Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
        [ Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
0 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"vkeywitness" Proxy BabbageEra
p)]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
1 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"native_script" Proxy BabbageEra
p)]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
2 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"bootstrap_witness" Proxy BabbageEra
p)]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
3 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v1_script" Proxy BabbageEra
p)]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
4 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_data" Proxy BabbageEra
p)]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
5 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"redeemers" Proxy BabbageEra
p
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
6 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v2_script" Proxy BabbageEra
p)]
        ]

instance HuddleRule "native_script" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era.
(HuddleGroup "script_pubkey" era, HuddleGroup "script_all" era,
 HuddleGroup "script_any" era, HuddleGroup "script_n_of_k" era,
 HuddleGroup "script_invalid_before" era,
 HuddleGroup "script_invalid_hereafter" era) =>
Proxy era -> Rule
nativeScriptRule @BabbageEra

instance HuddleGroup "script_pubkey" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptPubkeyGroup @BabbageEra

instance HuddleGroup "script_all" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
HuddleRule "native_script" era =>
Proxy era -> Named Group
scriptAllGroup @BabbageEra

instance HuddleGroup "script_any" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
HuddleRule "native_script" era =>
Proxy era -> Named Group
scriptAnyGroup @BabbageEra

instance HuddleGroup "script_n_of_k" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era.
(HuddleRule "int64" era, HuddleRule "native_script" era) =>
Proxy era -> Named Group
scriptNOfKGroup @BabbageEra

instance HuddleGroup "script_invalid_before" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptInvalidBeforeGroup @BabbageEra

instance HuddleGroup "script_invalid_hereafter" BabbageEra where
  huddleGroup :: Proxy BabbageEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptInvalidHereafterGroup @BabbageEra

instance HuddleRule "plutus_data" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era.
(HuddleRule "plutus_data" era, HuddleRule "bounded_bytes" era,
 HuddleRule "big_int" era) =>
Proxy era -> Rule
plutusDataRule

instance HuddleRule "plutus_v2_script" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|Babbage introduces Plutus V2 with improved cost model
          |and additional builtins.
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"plutus_v2_script" Text -> Rule -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"distinct_bytes" Proxy BabbageEra
p

instance HuddleRule "script" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = Proxy BabbageEra -> Rule
forall era.
(HuddleRule "native_script" era, HuddleRule "plutus_v1_script" era,
 HuddleRule "plutus_v2_script" era) =>
Proxy era -> Rule
babbageScript

babbageScript ::
  forall era.
  ( HuddleRule "native_script" era
  , HuddleRule "plutus_v1_script" era
  , HuddleRule "plutus_v2_script" era
  ) =>
  Proxy era -> Rule
babbageScript :: forall era.
(HuddleRule "native_script" era, HuddleRule "plutus_v1_script" era,
 HuddleRule "plutus_v2_script" era) =>
Proxy era -> Rule
babbageScript Proxy era
p =
  Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
    Text
[str|Babbage supports three script types:
        |  0: Native scripts (timelock)
        |  1: Plutus V1 scripts
        |  2: Plutus V2 scripts
        |]
    (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"script"
      Text -> Array -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
0, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"native_script" Proxy era
p)]
      ArrayChoice -> ArrayChoice -> Array
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
1, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v1_script" Proxy era
p)]
      Array -> ArrayChoice -> Array
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
2, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v2_script" Proxy era
p)]

instance HuddleRule "language" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
_ =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|0: Plutus v1
          |1: Plutus v2
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"language" Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Integer -> Literal
int Integer
0 Literal -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Integer -> Literal
int Integer
1

instance HuddleRule "cost_models" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"cost_models"
      Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
        [ Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
0 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
166 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"int64" Proxy BabbageEra
p) ArrayEntry -> Word64 -> ArrayEntry
forall a. CanQuantify a => a -> Word64 -> a
+> Word64
166]
        , Item MapChoice -> Item MapChoice
forall a. CanQuantify a => a -> a
opt (Item MapChoice -> Item MapChoice)
-> Item MapChoice -> Item MapChoice
forall a b. (a -> b) -> a -> b
$ Word64 -> Key
idx Word64
1 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
175 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"int64" Proxy BabbageEra
p) ArrayEntry -> Word64 -> ArrayEntry
forall a. CanQuantify a => a -> Word64 -> a
+> Word64
175]
        ]

instance HuddleRule "protocol_param_update" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"protocol_param_update"
      Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
        [ MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
0 Key -> Value Int -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"minfee A"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
1 Key -> Value Int -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"minfee B"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
2 Key -> Constrained -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> (Value Int
VUInt Value Int -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
4 :: Word64))) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max block body size"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
3 Key -> Constrained -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> (Value Int
VUInt Value Int -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
4 :: Word64))) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max transaction size"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
4 Key -> Constrained -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> (Value Int
VUInt Value Int -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
2 :: Word64))) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max block header size"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
5 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"key deposit"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
6 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"pool deposit"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
7 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"epoch_interval" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"maximum epoch"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
8 Key -> Constrained -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt Value Int -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
2 :: Word64)) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"n_opt: desired number of stake pools"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
9 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"nonnegative_interval" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"pool pledge influence"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
10 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"unit_interval" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"expansion rate"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
11 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"unit_interval" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"treasury growth rate"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
14 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"protocol_version" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"protocol version"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
16 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"min pool cost"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
17 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"coin" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"ada per utxo byte"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
18 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"cost_models" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"cost models for script languages"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
19 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"ex_unit_prices" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"execution costs"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
20 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"ex_units" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max tx ex units"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
21 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"ex_units" Proxy BabbageEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max block ex units"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
22 Key -> Value Int -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max value size"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
23 Key -> Value Int -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"collateral percentage"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
24 Key -> Value Int -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"max collateral inputs"
        ]

instance HuddleRule "auxiliary_data" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
      Text
[str|auxiliary_data supports three serialization formats:
          |  1. metadata (raw) - Supported since Shelley
          |  2. auxiliary_data_array - Array format, introduced in Allegra
          |  3. auxiliary_data_map - Tagged map format, introduced in Alonzo
          |     Babbage adds plutus_v2_script support at index 3
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"auxiliary_data"
        Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"metadata" Proxy BabbageEra
p
        Rule -> Rule -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"auxiliary_data_array" Proxy BabbageEra
p
        Choice Type2 -> Rule -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"auxiliary_data_map" Proxy BabbageEra
p

instance HuddleRule "auxiliary_data_array" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule = forall era. HuddleRule "auxiliary_scripts" era => Proxy era -> Rule
auxiliaryDataArrayRule @BabbageEra

instance HuddleRule "auxiliary_scripts" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"auxiliary_scripts" Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"native_script" Proxy BabbageEra
p)]

instance HuddleRule "auxiliary_data_map" BabbageEra where
  huddleRule :: Proxy BabbageEra -> Rule
huddleRule Proxy BabbageEra
p =
    Text
"auxiliary_data_map"
      Text -> Tagged MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Word64 -> MapChoice -> Tagged MapChoice
forall a. Word64 -> a -> Tagged a
tag
        Word64
259
        ( MapChoice -> MapChoice
mp
            [ MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
0 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"metadata" Proxy BabbageEra
p)
            , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
1 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"native_script" Proxy BabbageEra
p)])
            , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
2 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v1_script" Proxy BabbageEra
p)])
            , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
3 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v2_script" Proxy BabbageEra
p)])
            ]
        )