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

module Cardano.Ledger.Alonzo.HuddleSpec (
  module Cardano.Ledger.Mary.HuddleSpec,
  AlonzoEra,
  alonzoCDDL,
  constr,
  exUnitsRule,
  networkIdRule,
  positiveIntervalRule,
  bigUintRule,
  bigNintRule,
  bigIntRule,
  scriptDataHashRule,
  boundedBytesRule,
  distinctBytesRule,
  alonzoRedeemer,
  alonzoRedeemerTag,
  exUnitPricesRule,
  requiredSignersRule,
) where

import Cardano.Ledger.Alonzo (AlonzoEra)
import Cardano.Ledger.Mary.HuddleSpec
import Data.Proxy (Proxy (..))
import Data.Word (Word64)
import Text.Heredoc
import Prelude hiding ((/))

alonzoCDDL :: Huddle
alonzoCDDL :: Huddle
alonzoCDDL =
  [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 @AlonzoEra)
    , 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 @AlonzoEra)
    , 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 @AlonzoEra)
    , 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 @AlonzoEra)
    , 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 @AlonzoEra)
    ]

exUnitsRule :: Proxy "ex_units" -> Rule
exUnitsRule :: Proxy "ex_units" -> Rule
exUnitsRule Proxy "ex_units"
pname = Proxy "ex_units"
pname Proxy "ex_units" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= ArrayChoice -> ArrayChoice
arr [Key
"mem" Key -> Value Int -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt, Key
"steps" Key -> Value Int -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Value Int
VUInt]

networkIdRule :: Proxy "network_id" -> Rule
networkIdRule :: Proxy "network_id" -> Rule
networkIdRule Proxy "network_id"
pname = Proxy "network_id"
pname Proxy "network_id" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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

positiveIntervalRule ::
  forall era. Era era => Proxy "positive_interval" -> Proxy era -> Rule
positiveIntervalRule :: forall era.
Era era =>
Proxy "positive_interval" -> Proxy era -> Rule
positiveIntervalRule Proxy "positive_interval"
pname Proxy era
p =
  Proxy "positive_interval"
pname
    Proxy "positive_interval" -> Tagged ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
30 (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 @"positive_int" Proxy era
p), Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_int" Proxy era
p)])

bigUintRule ::
  forall era.
  HuddleRule "bounded_bytes" era => Proxy "big_uint" -> Proxy era -> Rule
bigUintRule :: forall era.
HuddleRule "bounded_bytes" era =>
Proxy "big_uint" -> Proxy era -> Rule
bigUintRule Proxy "big_uint"
pname Proxy era
p = Proxy "big_uint"
pname Proxy "big_uint" -> Tagged Rule -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Word64 -> Rule -> Tagged Rule
forall a. Word64 -> a -> Tagged a
tag Word64
2 (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"bounded_bytes" Proxy era
p)

bigNintRule ::
  forall era.
  HuddleRule "bounded_bytes" era => Proxy "big_nint" -> Proxy era -> Rule
bigNintRule :: forall era.
HuddleRule "bounded_bytes" era =>
Proxy "big_nint" -> Proxy era -> Rule
bigNintRule Proxy "big_nint"
pname Proxy era
p = Proxy "big_nint"
pname Proxy "big_nint" -> Tagged Rule -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Word64 -> Rule -> Tagged Rule
forall a. Word64 -> a -> Tagged a
tag Word64
3 (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"bounded_bytes" Proxy era
p)

bigIntRule ::
  forall era.
  ( HuddleRule "big_uint" era
  , HuddleRule "big_nint" era
  ) =>
  Proxy "big_int" ->
  Proxy era ->
  Rule
bigIntRule :: forall era.
(HuddleRule "big_uint" era, HuddleRule "big_nint" era) =>
Proxy "big_int" -> Proxy era -> Rule
bigIntRule Proxy "big_int"
pname Proxy era
p = Proxy "big_int"
pname Proxy "big_int" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Value Int
VInt Value Int -> 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 @"big_uint" Proxy era
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 @"big_nint" Proxy era
p

scriptDataHashRule ::
  forall era. Era era => Proxy "script_data_hash" -> Proxy era -> Rule
scriptDataHashRule :: forall era.
Era era =>
Proxy "script_data_hash" -> Proxy era -> Rule
scriptDataHashRule Proxy "script_data_hash"
pname Proxy era
p = Proxy "script_data_hash"
pname Proxy "script_data_hash" -> Rule -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"hash32" Proxy era
p

boundedBytesRule :: Proxy "bounded_bytes" -> Rule
boundedBytesRule :: Proxy "bounded_bytes" -> Rule
boundedBytesRule Proxy "bounded_bytes"
pname =
  Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
    Comment
[str|The real bounded_bytes does not have this limit. it instead has
        |a different limit which cannot be expressed in CDDL.
        |
        |The limit is as follows:
        | - bytes with a definite-length encoding are limited to size 0..64
        | - for bytes with an indefinite-length CBOR encoding, each chunk is
        |   limited to size 0..64
        | ( reminder: in CBOR, the indefinite-length encoding of
        | bytestrings consists of a token #2.31 followed by a sequence
        | of definite-length encoded bytestrings and a stop code )
        |]
    (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "bounded_bytes"
pname Proxy "bounded_bytes" -> Constrained -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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
64 :: Word64)

distinctBytesRule :: Proxy "distinct_bytes" -> Rule
distinctBytesRule :: Proxy "distinct_bytes" -> Rule
distinctBytesRule Proxy "distinct_bytes"
pname =
  Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
    Comment
[str|A type for distinct values.
        |The type parameter must support .size, for example: bytes or uint
        |]
    (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "distinct_bytes"
pname
      Proxy "distinct_bytes" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
8 :: Word64))
      Constrained -> Constrained -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
16 :: Word64))
      Choice Type2 -> Constrained -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
20 :: Word64))
      Choice Type2 -> Constrained -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
24 :: Word64))
      Choice Type2 -> Constrained -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
30 :: Word64))
      Choice Type2 -> Constrained -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Value ByteString
VBytes Value ByteString -> Word64 -> Constrained
forall c a s.
(IsSizeable a, IsSize s, IsConstrainable c a) =>
c -> s -> Constrained
`sized` (Word64
32 :: Word64))

exUnitPricesRule ::
  forall era.
  HuddleRule "positive_interval" era => Proxy "ex_unit_prices" -> Proxy era -> Rule
exUnitPricesRule :: forall era.
HuddleRule "positive_interval" era =>
Proxy "ex_unit_prices" -> Proxy era -> Rule
exUnitPricesRule Proxy "ex_unit_prices"
pname Proxy era
p =
  Proxy "ex_unit_prices"
pname
    Proxy "ex_unit_prices" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 era
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 era
p
      ]

requiredSignersRule ::
  forall era.
  (HuddleRule "addr_keyhash" era, HuddleRule1 "set" era) =>
  Proxy "required_signers" -> Proxy era -> Rule
requiredSignersRule :: forall era.
(HuddleRule "addr_keyhash" era, HuddleRule1 "set" era) =>
Proxy "required_signers" -> Proxy era -> Rule
requiredSignersRule Proxy "required_signers"
pname Proxy era
p = Proxy "required_signers"
pname Proxy "required_signers" -> GRuleCall -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era a.
(HuddleRule1 name era, IsType0 a) =>
Proxy era -> a -> GRuleCall
huddleRule1 @"set" Proxy era
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"addr_keyhash" Proxy era
p)

constr :: IsType0 a => Proxy "constr" -> a -> GRuleCall
constr :: forall a. IsType0 a => Proxy "constr" -> a -> GRuleCall
constr Proxy "constr"
pname =
  (GRef -> Rule) -> a -> GRuleCall
forall t0. IsType0 t0 => (GRef -> Rule) -> t0 -> GRuleCall
binding ((GRef -> Rule) -> a -> GRuleCall)
-> (GRef -> Rule) -> a -> GRuleCall
forall a b. (a -> b) -> a -> b
$ \GRef
x ->
    Proxy "constr"
pname
      Proxy "constr" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
121 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Tagged ArrayChoice -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
122 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
123 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
124 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
125 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
126 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
127 (ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x])
      Choice Type2 -> Tagged ArrayChoice -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Word64 -> ArrayChoice -> Tagged ArrayChoice
forall a. Word64 -> a -> Tagged a
tag Word64
102 (ArrayChoice -> ArrayChoice
arr [Value Int -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a Value Int
VUInt, ArrayChoice -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (ArrayChoice -> Item ArrayChoice)
-> ArrayChoice -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ ArrayChoice -> ArrayChoice
arr [Word64
0 Word64 -> ArrayEntry -> ArrayEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ GRef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a GRef
x]])

instance HuddleGroup "operational_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "operational_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "operational_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "operational_cert" -> Proxy era -> GroupDef
shelleyOperationalCertGroup

instance HuddleRule "transaction_id" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction_id" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "transaction_id" -> Proxy AlonzoEra -> Rule
forall era. Era era => Proxy "transaction_id" -> Proxy era -> Rule
transactionIdRule

instance HuddleRule "transaction_input" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction_input" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "transaction_input" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "transaction_id" era =>
Proxy "transaction_input" -> Proxy era -> Rule
transactionInputRule

instance HuddleRule "certificate" AlonzoEra where
  huddleRuleNamed :: Proxy "certificate" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "certificate" -> Proxy AlonzoEra -> Rule
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 "certificate" -> Proxy era -> Rule
certificateRule

instance HuddleGroup "account_registration_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "account_registration_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "account_registration_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "account_registration_cert" -> Proxy era -> GroupDef
accountRegistrationCertGroup

instance HuddleGroup "account_unregistration_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "account_unregistration_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "account_unregistration_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "account_unregistration_cert" -> Proxy era -> GroupDef
accountUnregistrationCertGroup

instance HuddleGroup "delegation_to_stake_pool_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "delegation_to_stake_pool_cert"
-> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "delegation_to_stake_pool_cert"
-> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "delegation_to_stake_pool_cert" -> Proxy era -> GroupDef
delegationToStakePoolCertGroup

instance HuddleGroup "pool_registration_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "pool_registration_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "pool_registration_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleGroup "pool_params" era =>
Proxy "pool_registration_cert" -> Proxy era -> GroupDef
poolRegistrationCertGroup

instance HuddleGroup "pool_retirement_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "pool_retirement_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "pool_retirement_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "pool_retirement_cert" -> Proxy era -> GroupDef
poolRetirementCertGroup

instance HuddleGroup "genesis_delegation_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "genesis_delegation_cert" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "genesis_delegation_cert" -> Proxy AlonzoEra -> GroupDef
forall era.
(HuddleRule "genesis_hash" era,
 HuddleRule "genesis_delegate_hash" era) =>
Proxy "genesis_delegation_cert" -> Proxy era -> GroupDef
genesisDelegationCertGroup

instance HuddleGroup "move_instantaneous_rewards_cert" AlonzoEra where
  huddleGroupNamed :: Proxy "move_instantaneous_rewards_cert"
-> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "move_instantaneous_rewards_cert"
-> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "move_instantaneous_reward" era =>
Proxy "move_instantaneous_rewards_cert" -> Proxy era -> GroupDef
moveInstantaneousRewardsCertGroup

instance HuddleRule "withdrawals" AlonzoEra where
  huddleRuleNamed :: Proxy "withdrawals" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "withdrawals" -> Proxy AlonzoEra -> Rule
forall era. Era era => Proxy "withdrawals" -> Proxy era -> Rule
shelleyWithdrawalsRule

instance HuddleRule "genesis_hash" AlonzoEra where
  huddleRuleNamed :: Proxy "genesis_hash" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "genesis_hash" -> Proxy AlonzoEra -> Rule
forall era. Era era => Proxy "genesis_hash" -> Proxy era -> Rule
genesisHashRule

instance HuddleRule "genesis_delegate_hash" AlonzoEra where
  huddleRuleNamed :: Proxy "genesis_delegate_hash" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "genesis_delegate_hash" -> Proxy AlonzoEra -> Rule
forall era.
Era era =>
Proxy "genesis_delegate_hash" -> Proxy era -> Rule
genesisDelegateHashRule

instance HuddleGroup "pool_params" AlonzoEra where
  huddleGroupNamed :: Proxy "pool_params" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "pool_params" -> Proxy AlonzoEra -> GroupDef
forall era.
(HuddleRule "relay" era, HuddleRule "pool_metadata" era,
 HuddleRule1 "set" era) =>
Proxy "pool_params" -> Proxy era -> GroupDef
poolParamsGroup

instance HuddleRule "pool_metadata" AlonzoEra where
  huddleRuleNamed :: Proxy "pool_metadata" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "pool_metadata" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "url" era =>
Proxy "pool_metadata" -> Proxy era -> Rule
poolMetadataRule

instance HuddleRule "dns_name" AlonzoEra where
  huddleRuleNamed :: Proxy "dns_name" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "dns_name"
pname Proxy AlonzoEra
_ = Proxy "dns_name" -> Rule
dnsNameRule Proxy "dns_name"
pname

instance HuddleRule "url" AlonzoEra where
  huddleRuleNamed :: Proxy "url" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "url"
pname Proxy AlonzoEra
_ = Proxy "url" -> Rule
urlRule Proxy "url"
pname

instance HuddleGroup "single_host_addr" AlonzoEra where
  huddleGroupNamed :: Proxy "single_host_addr" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "single_host_addr" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "single_host_addr" -> Proxy era -> GroupDef
singleHostAddrGroup

instance HuddleGroup "single_host_name" AlonzoEra where
  huddleGroupNamed :: Proxy "single_host_name" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "single_host_name" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "dns_name" era =>
Proxy "single_host_name" -> Proxy era -> GroupDef
singleHostNameGroup

instance HuddleGroup "multi_host_name" AlonzoEra where
  huddleGroupNamed :: Proxy "multi_host_name" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "multi_host_name" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "dns_name" era =>
Proxy "multi_host_name" -> Proxy era -> GroupDef
multiHostNameGroup

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

instance HuddleRule "move_instantaneous_reward" AlonzoEra where
  huddleRuleNamed :: Proxy "move_instantaneous_reward" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "move_instantaneous_reward" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "delta_coin" era =>
Proxy "move_instantaneous_reward" -> Proxy era -> Rule
moveInstantaneousRewardRule

instance HuddleRule "delta_coin" AlonzoEra where
  huddleRuleNamed :: Proxy "delta_coin" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "delta_coin"
pname Proxy AlonzoEra
_ = Proxy "delta_coin" -> Rule
deltaCoinRule Proxy "delta_coin"
pname

instance HuddleRule "vkeywitness" AlonzoEra where
  huddleRuleNamed :: Proxy "vkeywitness" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "vkeywitness" -> Proxy AlonzoEra -> Rule
forall era. Era era => Proxy "vkeywitness" -> Proxy era -> Rule
vkeywitnessRule

instance HuddleRule "bootstrap_witness" AlonzoEra where
  huddleRuleNamed :: Proxy "bootstrap_witness" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "bootstrap_witness" -> Proxy AlonzoEra -> Rule
forall era.
Era era =>
Proxy "bootstrap_witness" -> Proxy era -> Rule
bootstrapWitnessRule

instance HuddleRule "auxiliary_scripts" AlonzoEra where
  huddleRuleNamed :: Proxy "auxiliary_scripts" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "auxiliary_scripts" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "native_script" era =>
Proxy "auxiliary_scripts" -> Proxy era -> Rule
auxiliaryScriptsRule

instance HuddleRule "auxiliary_data_array" AlonzoEra where
  huddleRuleNamed :: Proxy "auxiliary_data_array" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "auxiliary_data_array" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "auxiliary_scripts" era =>
Proxy "auxiliary_data_array" -> Proxy era -> Rule
auxiliaryDataArrayRule

instance HuddleGroup "script_pubkey" AlonzoEra where
  huddleGroupNamed :: Proxy "script_pubkey" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_pubkey" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "script_pubkey" -> Proxy era -> GroupDef
scriptPubkeyGroup

instance HuddleGroup "script_all" AlonzoEra where
  huddleGroupNamed :: Proxy "script_all" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_all" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "native_script" era =>
Proxy "script_all" -> Proxy era -> GroupDef
scriptAllGroup

instance HuddleGroup "script_any" AlonzoEra where
  huddleGroupNamed :: Proxy "script_any" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_any" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "native_script" era =>
Proxy "script_any" -> Proxy era -> GroupDef
scriptAnyGroup

instance HuddleGroup "script_n_of_k" AlonzoEra where
  huddleGroupNamed :: Proxy "script_n_of_k" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_n_of_k" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "native_script" era =>
Proxy "script_n_of_k" -> Proxy era -> GroupDef
scriptNOfKGroup

instance HuddleGroup "script_invalid_before" AlonzoEra where
  huddleGroupNamed :: Proxy "script_invalid_before" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_invalid_before" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "script_invalid_before" -> Proxy era -> GroupDef
scriptInvalidBeforeGroup

instance HuddleGroup "script_invalid_hereafter" AlonzoEra where
  huddleGroupNamed :: Proxy "script_invalid_hereafter" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "script_invalid_hereafter" -> Proxy AlonzoEra -> GroupDef
forall era.
Era era =>
Proxy "script_invalid_hereafter" -> Proxy era -> GroupDef
scriptInvalidHereafterGroup

instance HuddleRule "policy_id" AlonzoEra where
  huddleRuleNamed :: Proxy "policy_id" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "policy_id"
pname Proxy AlonzoEra
p = Proxy "policy_id"
pname Proxy "policy_id" -> Rule -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"script_hash" Proxy AlonzoEra
p

instance HuddleRule "asset_name" AlonzoEra where
  huddleRuleNamed :: Proxy "asset_name" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "asset_name"
pname Proxy AlonzoEra
_ = Proxy "asset_name"
pname Proxy "asset_name" -> Constrained -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 "native_script" AlonzoEra where
  huddleRuleNamed :: Proxy "native_script" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "native_script" -> Proxy AlonzoEra -> Rule
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 "native_script" -> Proxy era -> Rule
nativeScriptRule

instance HuddleRule "value" AlonzoEra where
  huddleRuleNamed :: Proxy "value" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "value" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule1 "multiasset" era =>
Proxy "value" -> Proxy era -> Rule
maryValueRule

instance HuddleRule "mint" AlonzoEra where
  huddleRuleNamed :: Proxy "mint" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "mint" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule1 "multiasset" era =>
Proxy "mint" -> Proxy era -> Rule
maryMintRule

instance HuddleRule "block" AlonzoEra where
  huddleRuleNamed :: Proxy "block" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "block"
pname Proxy AlonzoEra
p =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[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
$ Proxy "block"
pname
        Proxy "block" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
p)] ArrayEntry -> Comment -> ArrayEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
          ]

instance HuddleRule "header" AlonzoEra where
  huddleRuleNamed :: Proxy "header" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "header"
pname Proxy AlonzoEra
p =
    Proxy "header"
pname
      Proxy "header" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
p
        ]

instance HuddleRule "header_body" AlonzoEra where
  huddleRuleNamed :: Proxy "header_body" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "header_body"
pname Proxy AlonzoEra
p =
    Proxy "header_body"
pname
      Proxy "header_body" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
p
        , Key
"nonce_vrf" 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 AlonzoEra
p
        , Key
"leader_vrf" 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 AlonzoEra
p
        , 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 AlonzoEra
p ArrayEntry -> Comment -> ArrayEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"merkle triple root"
        , GroupDef -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (GroupDef -> Item ArrayChoice) -> GroupDef -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> GroupDef
huddleGroup @"operational_cert" Proxy AlonzoEra
p
        , GroupDef -> Item ArrayChoice
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (GroupDef -> Item ArrayChoice) -> GroupDef -> Item ArrayChoice
forall a b. (a -> b) -> a -> b
$ forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> GroupDef
huddleGroup @"protocol_version" Proxy AlonzoEra
p
        ]

instance HuddleGroup "protocol_version" AlonzoEra where
  huddleGroupNamed :: Proxy "protocol_version" -> Proxy AlonzoEra -> GroupDef
huddleGroupNamed = Proxy "protocol_version" -> Proxy AlonzoEra -> GroupDef
forall era.
HuddleRule "major_protocol_version" era =>
Proxy "protocol_version" -> Proxy era -> GroupDef
shelleyProtocolVersionGroup

instance HuddleRule "major_protocol_version" AlonzoEra where
  huddleRuleNamed :: Proxy "major_protocol_version" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "major_protocol_version" -> Proxy AlonzoEra -> Rule
forall era.
Era era =>
Proxy "major_protocol_version" -> Proxy era -> Rule
majorProtocolVersionRule

instance HuddleRule "transaction" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "transaction"
pname Proxy AlonzoEra
p =
    Proxy "transaction"
pname
      Proxy "transaction" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction_body" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "transaction_body"
pname Proxy AlonzoEra
p =
    Proxy "transaction_body"
pname
      Proxy "transaction_body" -> MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= MapChoice -> MapChoice
mp
        [ Word64 -> Key
idx Word64
0 Key -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era a.
(HuddleRule1 name era, IsType0 a) =>
Proxy era -> a -> GRuleCall
huddleRule1 @"set" Proxy AlonzoEra
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
        , 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
==> forall (name :: Symbol) era a.
(HuddleRule1 name era, IsType0 a) =>
Proxy era -> a -> GRuleCall
huddleRule1 @"set" Proxy AlonzoEra
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy AlonzoEra
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 AlonzoEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
        , 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 AlonzoEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
        ]

instance HuddleRule "transaction_output" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction_output" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "transaction_output"
pname Proxy AlonzoEra
p =
    Proxy "transaction_output"
pname
      Proxy "transaction_output" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
p)
        ]

instance HuddleRule "update" AlonzoEra where
  huddleRuleNamed :: Proxy "update" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "update"
pname Proxy AlonzoEra
p =
    Proxy "update"
pname
      Proxy "update" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 @"proposed_protocol_parameter_updates" Proxy AlonzoEra
p)
        , Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"epoch" Proxy AlonzoEra
p)
        ]

instance HuddleRule "proposed_protocol_parameter_updates" AlonzoEra where
  huddleRuleNamed :: Proxy "proposed_protocol_parameter_updates"
-> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "proposed_protocol_parameter_updates"
pname Proxy AlonzoEra
p =
    Proxy "proposed_protocol_parameter_updates"
pname
      Proxy "proposed_protocol_parameter_updates" -> MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= 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 @"genesis_hash" Proxy AlonzoEra
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 @"protocol_param_update" Proxy AlonzoEra
p
        ]

instance HuddleRule "protocol_param_update" AlonzoEra where
  huddleRuleNamed :: Proxy "protocol_param_update" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "protocol_param_update"
pname Proxy AlonzoEra
p =
    Proxy "protocol_param_update"
pname
      Proxy "protocol_param_update" -> MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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
12 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 AlonzoEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"decentralization constant"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
13 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"nonce" Proxy AlonzoEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"extra entropy"
        , MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
14 Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr [GroupDef -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> GroupDef
huddleGroup @"protocol_version" Proxy AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 "transaction_witness_set" AlonzoEra where
  huddleRuleNamed :: Proxy "transaction_witness_set" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "transaction_witness_set"
pname Proxy AlonzoEra
p =
    Proxy "transaction_witness_set"
pname
      Proxy "transaction_witness_set" -> MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
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
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 AlonzoEra
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
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 AlonzoEra
p MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"new"
        ]

instance HuddleRule "auxiliary_data" AlonzoEra where
  huddleRuleNamed :: Proxy "auxiliary_data" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "auxiliary_data"
pname Proxy AlonzoEra
p =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[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
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "auxiliary_data"
pname
        Proxy "auxiliary_data" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"metadata" Proxy AlonzoEra
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 AlonzoEra
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 AlonzoEra
p

instance HuddleRule "auxiliary_data_map" AlonzoEra where
  huddleRuleNamed :: Proxy "auxiliary_data_map" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "auxiliary_data_map"
pname Proxy AlonzoEra
p =
    Proxy "auxiliary_data_map"
pname
      Proxy "auxiliary_data_map" -> Tagged MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
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 AlonzoEra
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 AlonzoEra
p)])
            ]
        )

instance HuddleRule "script_data_hash" AlonzoEra where
  huddleRuleNamed :: Proxy "script_data_hash" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "script_data_hash"
pname Proxy AlonzoEra
p =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[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 cost_models 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 cost_models map at key 0 is encoded as an indefinite length
          |    list and the result is encoded as a bytestring. (our apologies)
          |  - the language ID tag is also encoded twice. first as a uint then as
          |    a bytestring. (our apologies)
          |
          |Note that each Plutus language represented inside a transaction
          |must have a cost model in the cost_models protocol parameter in
          |order to execute, regardless of what the script integrity data
          |is. In the Alonzo era, this means cost_models must have a key 0
          |for Plutus V1.
          |
          |Finally, note that in the case that a transaction includes
          |datums but does not include any redeemers, the script data
          |format becomes (in hex):
          |  [ 80 | datums | A0 ]
          |
          |corresponding to a CBOR empty list and an empty map (our
          |apologies).
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "script_data_hash" -> Proxy AlonzoEra -> Rule
forall era.
Era era =>
Proxy "script_data_hash" -> Proxy era -> Rule
scriptDataHashRule Proxy "script_data_hash"
pname Proxy AlonzoEra
p

instance HuddleRule "required_signers" AlonzoEra where
  huddleRuleNamed :: Proxy "required_signers" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "required_signers" -> Proxy AlonzoEra -> Rule
forall era.
(HuddleRule "addr_keyhash" era, HuddleRule1 "set" era) =>
Proxy "required_signers" -> Proxy era -> Rule
requiredSignersRule

instance HuddleRule "network_id" AlonzoEra where
  huddleRuleNamed :: Proxy "network_id" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "network_id"
pname Proxy AlonzoEra
_ = Proxy "network_id" -> Rule
networkIdRule Proxy "network_id"
pname

instance (Era era, HuddleRule "distinct_bytes" era) => HuddleRule "plutus_v1_script" era where
  huddleRuleNamed :: Proxy "plutus_v1_script" -> Proxy era -> Rule
huddleRuleNamed Proxy "plutus_v1_script"
pname Proxy era
p =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[str|Alonzo introduces Plutus smart contracts.
          |Plutus V1 scripts are opaque bytestrings.
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "plutus_v1_script"
pname Proxy "plutus_v1_script" -> Rule -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"distinct_bytes" Proxy era
p

instance HuddleRule "distinct_bytes" AlonzoEra where
  huddleRuleNamed :: Proxy "distinct_bytes" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "distinct_bytes"
pname Proxy AlonzoEra
_ = Proxy "distinct_bytes" -> Rule
distinctBytesRule Proxy "distinct_bytes"
pname

instance HuddleRule "bounded_bytes" AlonzoEra where
  huddleRuleNamed :: Proxy "bounded_bytes" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "bounded_bytes"
pname Proxy AlonzoEra
_ = Proxy "bounded_bytes" -> Rule
boundedBytesRule Proxy "bounded_bytes"
pname

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

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

instance HuddleRule "big_int" AlonzoEra where
  huddleRuleNamed :: Proxy "big_int" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "big_int" -> Proxy AlonzoEra -> Rule
forall era.
(HuddleRule "big_uint" era, HuddleRule "big_nint" era) =>
Proxy "big_int" -> Proxy era -> Rule
bigIntRule

instance
  (Era era, HuddleRule "big_int" era, HuddleRule "bounded_bytes" era, HuddleRule1 "constr" era) =>
  HuddleRule "plutus_data" era
  where
  huddleRuleNamed :: Proxy "plutus_data" -> Proxy era -> Rule
huddleRuleNamed Proxy "plutus_data"
pname Proxy era
p =
    Proxy "plutus_data"
pname
      Proxy "plutus_data" -> Choice Type2 -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= forall (name :: Symbol) era a.
(HuddleRule1 name era, IsType0 a) =>
Proxy era -> a -> GRuleCall
huddleRule1 @"constr" Proxy era
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_data" Proxy era
p)
      GRuleCall -> Seal Map -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ MapChoice -> Seal Map
smp [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 @"plutus_data" Proxy era
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 @"plutus_data" Proxy era
p]
      Choice Type2 -> Seal Array -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> Seal Array
sarr [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 era
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 @"big_int" Proxy era
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 @"bounded_bytes" Proxy era
p

instance Era era => HuddleRule1 "constr" era where
  huddleRule1Named :: forall a.
IsType0 a =>
Proxy "constr" -> Proxy era -> a -> GRuleCall
huddleRule1Named Proxy "constr"
pname Proxy era
_ = Proxy "constr" -> a -> GRuleCall
forall a. IsType0 a => Proxy "constr" -> a -> GRuleCall
constr Proxy "constr"
pname

instance HuddleRule "redeemers" AlonzoEra where
  huddleRuleNamed :: Proxy "redeemers" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "redeemers"
pname Proxy AlonzoEra
p = Proxy "redeemers"
pname Proxy "redeemers" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 AlonzoEra
p)]

alonzoRedeemer ::
  forall era.
  ( HuddleRule "redeemer_tag" era
  , HuddleRule "plutus_data" era
  , HuddleRule "ex_units" era
  ) =>
  Proxy "redeemer" ->
  Proxy era ->
  Rule
alonzoRedeemer :: forall era.
(HuddleRule "redeemer_tag" era, HuddleRule "plutus_data" era,
 HuddleRule "ex_units" era) =>
Proxy "redeemer" -> Proxy era -> Rule
alonzoRedeemer Proxy "redeemer"
pname Proxy era
p =
  Proxy "redeemer"
pname
    Proxy "redeemer" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> 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 era
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 era
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 era
p
      ]

instance HuddleRule "redeemer" AlonzoEra where
  huddleRuleNamed :: Proxy "redeemer" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "redeemer" -> Proxy AlonzoEra -> Rule
forall era.
(HuddleRule "redeemer_tag" era, HuddleRule "plutus_data" era,
 HuddleRule "ex_units" era) =>
Proxy "redeemer" -> Proxy era -> Rule
alonzoRedeemer

alonzoRedeemerTag :: Proxy "redeemer_tag" -> Rule
alonzoRedeemerTag :: Proxy "redeemer_tag" -> Rule
alonzoRedeemerTag Proxy "redeemer_tag"
pname =
  Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
    Comment
[str|0: spend
        |1: mint
        |2: cert
        |3: reward
        |]
    (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "redeemer_tag"
pname Proxy "redeemer_tag" -> Ranged -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= (Integer
0 :: Integer) Integer -> Integer -> Ranged
forall a b. (IsRangeBound a, IsRangeBound b) => a -> b -> Ranged
... (Integer
3 :: Integer)

instance HuddleRule "redeemer_tag" AlonzoEra where
  huddleRuleNamed :: Proxy "redeemer_tag" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "redeemer_tag"
pname Proxy AlonzoEra
_ = Proxy "redeemer_tag" -> Rule
alonzoRedeemerTag Proxy "redeemer_tag"
pname

instance HuddleRule "ex_units" AlonzoEra where
  huddleRuleNamed :: Proxy "ex_units" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "ex_units"
pname Proxy AlonzoEra
_ = Proxy "ex_units" -> Rule
exUnitsRule Proxy "ex_units"
pname

instance HuddleRule "ex_unit_prices" AlonzoEra where
  huddleRuleNamed :: Proxy "ex_unit_prices" -> Proxy AlonzoEra -> Rule
huddleRuleNamed = Proxy "ex_unit_prices" -> Proxy AlonzoEra -> Rule
forall era.
HuddleRule "positive_interval" era =>
Proxy "ex_unit_prices" -> Proxy era -> Rule
exUnitPricesRule

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

instance HuddleRule "language" AlonzoEra where
  huddleRuleNamed :: Proxy "language" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "language"
pname Proxy AlonzoEra
_ =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[str|NOTE: NEW
          |  This is an enumeration. for now there's only one value. Plutus V1
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "language"
pname Proxy "language" -> Literal -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= Integer -> Literal
int Integer
0

instance HuddleRule "cost_models" AlonzoEra where
  huddleRuleNamed :: Proxy "cost_models" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "cost_models"
pname Proxy AlonzoEra
p =
    Proxy "cost_models"
pname
      Proxy "cost_models" -> MapChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= 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 @"language" Proxy AlonzoEra
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 @"cost_model" Proxy AlonzoEra
p]

instance HuddleRule "cost_model" AlonzoEra where
  huddleRuleNamed :: Proxy "cost_model" -> Proxy AlonzoEra -> Rule
huddleRuleNamed Proxy "cost_model"
pname Proxy AlonzoEra
p =
    Comment -> Rule -> Rule
forall a. HasComment a => Comment -> a -> a
comment
      Comment
[str|NOTE: NEW
          |  The keys to the cost model map are not present in the serialization.
          |  The values in the serialization are assumed to be ordered
          |  lexicographically by their correpsonding key value.
          |  See Plutus' `ParamName` for parameter ordering
          |]
      (Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy "cost_model"
pname Proxy "cost_model" -> ArrayChoice -> Rule
forall (name :: Symbol) t.
(KnownSymbol name, IsType0 t) =>
Proxy name -> t -> Rule
=.= 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 AlonzoEra
p) ArrayEntry -> Word64 -> ArrayEntry
forall a. CanQuantify a => a -> Word64 -> a
+> Word64
166]

instance HuddleRule1 "set" AlonzoEra where
  huddleRule1Named :: forall a.
IsType0 a =>
Proxy "set" -> Proxy AlonzoEra -> a -> GRuleCall
huddleRule1Named Proxy "set"
pname Proxy AlonzoEra
_ = Proxy "set" -> a -> GRuleCall
forall a. IsType0 a => Proxy "set" -> a -> GRuleCall
untaggedSet Proxy "set"
pname

instance HuddleRule1 "multiasset" AlonzoEra where
  huddleRule1Named :: forall a.
IsType0 a =>
Proxy "multiasset" -> Proxy AlonzoEra -> a -> GRuleCall
huddleRule1Named = Proxy "multiasset" -> Proxy AlonzoEra -> a -> GRuleCall
forall era a.
(HuddleRule "policy_id" era, HuddleRule "asset_name" era,
 IsType0 a) =>
Proxy "multiasset" -> Proxy era -> a -> GRuleCall
maryMultiasset