{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Ledger.Dijkstra.HuddleSpec (
module Cardano.Ledger.Conway.HuddleSpec,
dijkstraCDDL,
guardsRule,
subTransactionsRule,
subTransactionRule,
subTransactionBodyRule,
requiredTopLevelGuardsRule,
dijkstraScriptRule,
dijkstraNativeScriptRule,
scriptRequireGuardGroup,
dijkstraRedeemerTagRule,
auxiliaryDataMapRule,
) where
import Cardano.Ledger.Conway.HuddleSpec hiding ()
import Cardano.Ledger.Dijkstra (DijkstraEra)
import Codec.CBOR.Cuddle.Comments ((//-))
import Codec.CBOR.Cuddle.Huddle
import Data.Proxy (Proxy (..))
import Data.Text ()
import Data.Word (Word64)
import Text.Heredoc
import Prelude hiding ((/))
dijkstraCDDL :: Huddle
dijkstraCDDL :: Huddle
dijkstraCDDL =
[HuddleItem] -> Huddle
collectFromInit
[ 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 @DijkstraEra)
, 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 @DijkstraEra)
, 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 @DijkstraEra)
, 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 @DijkstraEra)
, 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 @"potential_languages" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @DijkstraEra)
, 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 @DijkstraEra)
, 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 @"certificate" (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @DijkstraEra)
]
guardsRule ::
forall era. (HuddleRule "addr_keyhash" era, HuddleRule "credential" era) => Proxy era -> Rule
guardsRule :: forall era.
(HuddleRule "addr_keyhash" era, HuddleRule "credential" era) =>
Proxy era -> Rule
guardsRule Proxy era
p =
Text
"guards"
Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"addr_keyhash" Proxy era
p)
GRuleCall -> GRuleCall -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptyOset (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"credential" Proxy era
p)
subTransactionsRule ::
forall era.
( HuddleRule "transaction_input" era
, HuddleRule "transaction_output" era
, HuddleRule "slot" era
, HuddleRule "certificates" era
, HuddleRule "withdrawals" era
, HuddleRule "auxiliary_data_hash" era
, HuddleRule "mint" era
, HuddleRule "script_data_hash" era
, HuddleRule "network_id" era
, HuddleRule "voting_procedures" era
, HuddleRule "proposal_procedures" era
, HuddleRule "coin" era
, HuddleRule "positive_coin" era
, HuddleRule "credential" era
, HuddleRule "plutus_data" era
, HuddleRule "transaction_witness_set" era
, HuddleRule "auxiliary_data" era
) =>
Proxy era ->
Rule
subTransactionsRule :: forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era,
HuddleRule "transaction_witness_set" era,
HuddleRule "auxiliary_data" era) =>
Proxy era -> Rule
subTransactionsRule Proxy era
p =
Text
"sub_transactions" Text -> GRuleCall -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptyOset (Proxy era -> Rule
forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era,
HuddleRule "transaction_witness_set" era,
HuddleRule "auxiliary_data" era) =>
Proxy era -> Rule
subTransactionRule Proxy era
p)
subTransactionRule ::
forall era.
( HuddleRule "transaction_input" era
, HuddleRule "transaction_output" era
, HuddleRule "slot" era
, HuddleRule "certificates" era
, HuddleRule "withdrawals" era
, HuddleRule "auxiliary_data_hash" era
, HuddleRule "mint" era
, HuddleRule "script_data_hash" era
, HuddleRule "network_id" era
, HuddleRule "voting_procedures" era
, HuddleRule "proposal_procedures" era
, HuddleRule "coin" era
, HuddleRule "positive_coin" era
, HuddleRule "credential" era
, HuddleRule "plutus_data" era
, HuddleRule "transaction_witness_set" era
, HuddleRule "auxiliary_data" era
) =>
Proxy era ->
Rule
subTransactionRule :: forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era,
HuddleRule "transaction_witness_set" era,
HuddleRule "auxiliary_data" era) =>
Proxy era -> Rule
subTransactionRule Proxy era
p =
Text
"sub_transaction"
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 (Proxy era -> Rule
forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era) =>
Proxy era -> Rule
subTransactionBodyRule 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 @"transaction_witness_set" Proxy era
p)
, 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 era
p Rule -> Value Void -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Value Void
VNil)
]
subTransactionBodyRule ::
forall era.
( HuddleRule "transaction_input" era
, HuddleRule "transaction_output" era
, HuddleRule "slot" era
, HuddleRule "certificates" era
, HuddleRule "withdrawals" era
, HuddleRule "auxiliary_data_hash" era
, HuddleRule "mint" era
, HuddleRule "script_data_hash" era
, HuddleRule "network_id" era
, HuddleRule "voting_procedures" era
, HuddleRule "proposal_procedures" era
, HuddleRule "coin" era
, HuddleRule "positive_coin" era
, HuddleRule "credential" era
, HuddleRule "plutus_data" era
) =>
Proxy era ->
Rule
subTransactionBodyRule :: forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era) =>
Proxy era -> Rule
subTransactionBodyRule Proxy era
p =
Text
"sub_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
maybeTaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy era
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 era
p)]
, 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 era
p)
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
4 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"certificates" Proxy era
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 era
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 era
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 era
p)
, 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 era
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 era
p)
, 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
==> Proxy era -> Rule
forall era.
(HuddleRule "addr_keyhash" era, HuddleRule "credential" era) =>
Proxy era -> Rule
guardsRule Proxy era
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 era
p)
, 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
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy era
p))
, 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 @"voting_procedures" Proxy era
p)
, 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 @"proposal_procedures" Proxy era
p)
, 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 @"coin" Proxy era
p)
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
22 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_coin" Proxy era
p)
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
24 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Proxy era -> Rule
forall era.
(HuddleRule "credential" era, HuddleRule "plutus_data" era) =>
Proxy era -> Rule
requiredTopLevelGuardsRule Proxy era
p)
]
requiredTopLevelGuardsRule ::
forall era.
( HuddleRule "credential" era
, HuddleRule "plutus_data" era
) =>
Proxy era ->
Rule
requiredTopLevelGuardsRule :: forall era.
(HuddleRule "credential" era, HuddleRule "plutus_data" era) =>
Proxy era -> Rule
requiredTopLevelGuardsRule Proxy era
p =
Text
"required_top_level_guards"
Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
[ Word64
1
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 @"credential" Proxy era
p)
Key -> Choice Type2 -> 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 Rule -> Value Void -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Value Void
VNil)
]
scriptRequireGuardGroup :: forall era. HuddleRule "credential" era => Proxy era -> Named Group
scriptRequireGuardGroup :: forall era. HuddleRule "credential" era => Proxy era -> Named Group
scriptRequireGuardGroup Proxy era
p =
Text -> Named Group -> Named Group
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|Dijkstra adds guard scripts for enhanced security.
|A guard script requires a credential to authorize execution.
|]
(Named Group -> Named Group) -> Named Group -> Named Group
forall a b. (a -> b) -> a -> b
$ Text
"script_require_guard" Text -> Group -> Named Group
=:~ Group -> Group
grp [Item Group
ArrayEntry
6, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"credential" Proxy era
p)]
dijkstraNativeScriptRule ::
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
, HuddleRule "credential" era
) =>
Proxy era ->
Rule
dijkstraNativeScriptRule :: 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,
HuddleRule "credential" era) =>
Proxy era -> Rule
dijkstraNativeScriptRule Proxy era
p =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|Dijkstra native scripts extend Allegra's 6-variant format
|with a 7th variant for guard scripts.
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"native_script"
Text -> Choice ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_pubkey" Proxy era
p)]
ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_all" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_any" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_n_of_k" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_invalid_before" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleGroup name era =>
Proxy era -> Named Group
huddleGroup @"script_invalid_hereafter" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Named Group -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (Proxy era -> Named Group
forall era. HuddleRule "credential" era => Proxy era -> Named Group
scriptRequireGuardGroup Proxy era
p)]
dijkstraScriptRule ::
forall era.
( HuddleRule "native_script" era
, HuddleRule "plutus_v1_script" era
, HuddleRule "plutus_v2_script" era
, HuddleRule "plutus_v3_script" era
, HuddleRule "plutus_v4_script" era
) =>
Proxy era ->
Rule
dijkstraScriptRule :: forall era.
(HuddleRule "native_script" era, HuddleRule "plutus_v1_script" era,
HuddleRule "plutus_v2_script" era,
HuddleRule "plutus_v3_script" era,
HuddleRule "plutus_v4_script" era) =>
Proxy era -> Rule
dijkstraScriptRule Proxy era
p =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|Dijkstra supports five script types:
| 0: Native scripts with guard support (7 variants)
| 1: Plutus V1 scripts
| 2: Plutus V2 scripts
| 3: Plutus V3 scripts
| 4: Plutus V4 scripts (NEW)
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"script"
Text -> Choice ArrayChoice -> 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 -> Choice ArrayChoice
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)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
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)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
3, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v3_script" Proxy era
p)]
Choice ArrayChoice -> ArrayChoice -> Choice ArrayChoice
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ ArrayChoice -> ArrayChoice
arr [Item ArrayChoice
ArrayEntry
4, Rule -> ArrayEntry
forall a e. (IsType0 a, IsGroupOrArrayEntry e) => a -> e
a (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v4_script" Proxy era
p)]
dijkstraRedeemerTagRule :: Proxy era -> Rule
dijkstraRedeemerTagRule :: forall era. Proxy era -> Rule
dijkstraRedeemerTagRule Proxy era
_ =
Text
"redeemer_tag"
Text -> Choice Type2 -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= (Integer -> Literal
int Integer
0 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"spend")
Literal -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
1 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"mint")
Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
2 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"cert")
Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
3 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"reward")
Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
4 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"voting")
Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
5 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"proposing")
Choice Type2 -> Literal -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ (Integer -> Literal
int Integer
6 Literal -> Comment -> Literal
forall a. HasComment a => a -> Comment -> a
//- Comment
"guarding")
auxiliaryDataMapRule ::
forall era.
( HuddleRule "metadata" era
, HuddleRule "native_script" era
, HuddleRule "plutus_v1_script" era
, HuddleRule "plutus_v2_script" era
, HuddleRule "plutus_v3_script" era
, HuddleRule "plutus_v4_script" era
) =>
Proxy era ->
Rule
auxiliaryDataMapRule :: forall era.
(HuddleRule "metadata" era, HuddleRule "native_script" era,
HuddleRule "plutus_v1_script" era,
HuddleRule "plutus_v2_script" era,
HuddleRule "plutus_v3_script" era,
HuddleRule "plutus_v4_script" era) =>
Proxy era -> Rule
auxiliaryDataMapRule Proxy era
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 era
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 era
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 era
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 era
p)])
, 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 @"plutus_v3_script" Proxy era
p)])
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
5 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_v4_script" Proxy era
p)])
]
)
instance HuddleRule "bounded_bytes" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Rule
boundedBytesRule
instance HuddleRule "distinct_bytes" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Rule
distinctBytesRule
instance HuddleRule "big_uint" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = Proxy DijkstraEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigUintRule
instance HuddleRule "big_nint" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = Proxy DijkstraEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigNintRule
instance HuddleRule "big_int" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = Proxy DijkstraEra -> Rule
forall era. HuddleRule "bounded_bytes" era => Proxy era -> Rule
bigIntRule
instance HuddleRule "network_id" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Rule
networkIdRule
instance HuddleRule "dns_name" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Proxy era -> Rule
dnsNameRule @DijkstraEra
instance HuddleRule "url" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Proxy era -> Rule
urlRule @DijkstraEra
instance HuddleRule "major_protocol_version" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
majorProtocolVersionRule @DijkstraEra
instance HuddleRule "genesis_hash" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
genesisHashRule @DijkstraEra
instance HuddleRule "genesis_delegate_hash" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
genesisDelegateHashRule @DijkstraEra
instance HuddleRule "transaction_id" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
transactionIdRule @DijkstraEra
instance HuddleRule "vkeywitness" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
vkeywitnessRule @DijkstraEra
instance HuddleRule "bootstrap_witness" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
bootstrapWitnessRule @DijkstraEra
instance HuddleRule "ex_units" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Rule
exUnitsRule
instance HuddleRule "positive_interval" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = Proxy DijkstraEra -> Rule
forall era. Era era => Proxy era -> Rule
positiveIntervalRule
instance HuddleRule "vote" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Proxy era -> Rule
voteRule @DijkstraEra
instance HuddleRule "asset_name" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Proxy era -> Rule
assetNameRule @DijkstraEra
instance HuddleRule "drep_credential" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "credential" era => Proxy era -> Rule
drepCredentialRule @DijkstraEra
instance HuddleRule "committee_cold_credential" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "credential" era => Proxy era -> Rule
committeeColdCredentialRule @DijkstraEra
instance HuddleRule "committee_hot_credential" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "credential" era => Proxy era -> Rule
committeeHotCredentialRule @DijkstraEra
instance HuddleRule "anchor" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "url" era, HuddleRule "hash32" era) =>
Proxy era -> Rule
anchorRule @DijkstraEra
instance HuddleRule "drep" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "addr_keyhash" era, HuddleRule "script_hash" era) =>
Proxy era -> Rule
drepRule @DijkstraEra
instance HuddleRule "voter" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "addr_keyhash" era, HuddleRule "script_hash" era) =>
Proxy era -> Rule
voterRule @DijkstraEra
instance HuddleRule "operational_cert" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
babbageOperationalCertRule @DijkstraEra
instance HuddleRule "protocol_version" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
HuddleRule "major_protocol_version" era =>
Proxy era -> Rule
babbageProtocolVersionRule @DijkstraEra
instance HuddleRule "policy_id" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 DijkstraEra
p
instance HuddleRule "policy_hash" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "script_hash" era => Proxy era -> Rule
policyHashRule @DijkstraEra
instance HuddleGroup "script_pubkey" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptPubkeyGroup @DijkstraEra
instance HuddleGroup "script_all" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
HuddleRule "native_script" era =>
Proxy era -> Named Group
scriptAllGroup @DijkstraEra
instance HuddleGroup "script_any" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
HuddleRule "native_script" era =>
Proxy era -> Named Group
scriptAnyGroup @DijkstraEra
instance HuddleGroup "script_n_of_k" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
HuddleRule "native_script" era =>
Proxy era -> Named Group
scriptNOfKGroup @DijkstraEra
instance HuddleGroup "script_invalid_before" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptInvalidBeforeGroup @DijkstraEra
instance HuddleGroup "script_invalid_hereafter" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
scriptInvalidHereafterGroup @DijkstraEra
instance HuddleGroup "single_host_addr" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
singleHostAddrGroup @DijkstraEra
instance HuddleGroup "single_host_name" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. HuddleRule "dns_name" era => Proxy era -> Named Group
singleHostNameGroup @DijkstraEra
instance HuddleGroup "multi_host_name" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. HuddleRule "dns_name" era => Proxy era -> Named Group
multiHostNameGroup @DijkstraEra
instance HuddleRule "relay" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleGroup "single_host_addr" era,
HuddleGroup "single_host_name" era,
HuddleGroup "multi_host_name" era) =>
Proxy era -> Rule
relayRule @DijkstraEra
instance HuddleRule "pool_metadata" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "url" era => Proxy era -> Rule
poolMetadataRule @DijkstraEra
instance HuddleGroup "pool_params" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "relay" era, HuddleRule "pool_metadata" era) =>
Proxy era -> Named Group
poolParamsGroup @DijkstraEra
instance HuddleGroup "account_registration_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
accountRegistrationCertGroup @DijkstraEra
instance HuddleGroup "account_unregistration_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
accountUnregistrationCertGroup @DijkstraEra
instance HuddleGroup "delegation_to_stake_pool_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
delegationToStakePoolCertGroup @DijkstraEra
instance HuddleGroup "pool_registration_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
HuddleGroup "pool_params" era =>
Proxy era -> Named Group
poolRegistrationCertGroup @DijkstraEra
instance HuddleGroup "pool_retirement_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era. Era era => Proxy era -> Named Group
poolRetirementCertGroup @DijkstraEra
instance HuddleGroup "account_registration_deposit_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "coin" era) =>
Proxy era -> Named Group
accountRegistrationDepositCertGroup @DijkstraEra
instance HuddleGroup "account_unregistration_deposit_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "coin" era) =>
Proxy era -> Named Group
accountUnregistrationDepositCertGroup @DijkstraEra
instance HuddleGroup "delegation_to_drep_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "drep" era) =>
Proxy era -> Named Group
delegationToDrepCertGroup @DijkstraEra
instance HuddleGroup "delegation_to_stake_pool_and_drep_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "pool_keyhash" era,
HuddleRule "drep" era) =>
Proxy era -> Named Group
delegationToStakePoolAndDrepCertGroup @DijkstraEra
instance HuddleGroup "account_registration_delegation_to_stake_pool_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "pool_keyhash" era,
HuddleRule "coin" era) =>
Proxy era -> Named Group
accountRegistrationDelegationToStakePoolCertGroup @DijkstraEra
instance HuddleGroup "account_registration_delegation_to_drep_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "drep" era,
HuddleRule "coin" era) =>
Proxy era -> Named Group
accountRegistrationDelegationToDrepCertGroup @DijkstraEra
instance HuddleGroup "account_registration_delegation_to_stake_pool_and_drep_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "stake_credential" era, HuddleRule "pool_keyhash" era,
HuddleRule "drep" era, HuddleRule "coin" era) =>
Proxy era -> Named Group
accountRegistrationDelegationToStakePoolAndDrepCertGroup @DijkstraEra
instance HuddleGroup "committee_authorization_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "committee_cold_credential" era,
HuddleRule "committee_hot_credential" era) =>
Proxy era -> Named Group
committeeAuthorizationCertGroup @DijkstraEra
instance HuddleGroup "committee_resignation_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "committee_cold_credential" era,
HuddleRule "anchor" era) =>
Proxy era -> Named Group
committeeResignationCertGroup @DijkstraEra
instance HuddleGroup "drep_registration_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "drep_credential" era, HuddleRule "coin" era,
HuddleRule "anchor" era) =>
Proxy era -> Named Group
drepRegistrationCertGroup @DijkstraEra
instance HuddleGroup "drep_unregistration_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "drep_credential" era, HuddleRule "coin" era) =>
Proxy era -> Named Group
drepUnregistrationCertGroup @DijkstraEra
instance HuddleGroup "drep_update_cert" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "drep_credential" era, HuddleRule "anchor" era) =>
Proxy era -> Named Group
drepUpdateCertGroup @DijkstraEra
instance HuddleRule "certificate" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> 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 "account_registration_deposit_cert" era,
HuddleGroup "account_unregistration_deposit_cert" era,
HuddleGroup "delegation_to_drep_cert" era,
HuddleGroup "delegation_to_stake_pool_and_drep_cert" era,
HuddleGroup
"account_registration_delegation_to_stake_pool_cert" era,
HuddleGroup "account_registration_delegation_to_drep_cert" era,
HuddleGroup
"account_registration_delegation_to_stake_pool_and_drep_cert" era,
HuddleGroup "committee_authorization_cert" era,
HuddleGroup "committee_resignation_cert" era,
HuddleGroup "drep_registration_cert" era,
HuddleGroup "drep_unregistration_cert" era,
HuddleGroup "drep_update_cert" era) =>
Proxy era -> Rule
conwayCertificateRule @DijkstraEra
instance HuddleRule "certificates" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "certificate" era => Proxy era -> Rule
certificatesRule @DijkstraEra
instance HuddleRule "voting_procedure" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "vote" era, HuddleRule "anchor" era) =>
Proxy era -> Rule
votingProcedureRule @DijkstraEra
instance HuddleRule "voting_procedures" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "voter" era, HuddleRule "gov_action_id" era,
HuddleRule "voting_procedure" era) =>
Proxy era -> Rule
votingProceduresRule @DijkstraEra
instance HuddleRule "constitution" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "anchor" era, HuddleRule "script_hash" era) =>
Proxy era -> Rule
constitutionRule @DijkstraEra
instance HuddleGroup "parameter_change_action" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "gov_action_id" era,
HuddleRule "protocol_param_update" era,
HuddleRule "policy_hash" era) =>
Proxy era -> Named Group
parameterChangeActionGroup @DijkstraEra
instance HuddleGroup "hard_fork_initiation_action" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "gov_action_id" era,
HuddleRule "protocol_version" era) =>
Proxy era -> Named Group
hardForkInitiationActionGroup @DijkstraEra
instance HuddleGroup "treasury_withdrawals_action" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "reward_account" era, HuddleRule "coin" era,
HuddleRule "policy_hash" era) =>
Proxy era -> Named Group
treasuryWithdrawalsActionGroup @DijkstraEra
instance HuddleGroup "no_confidence" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
HuddleRule "gov_action_id" era =>
Proxy era -> Named Group
noConfidenceGroup @DijkstraEra
instance HuddleGroup "update_committee" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "gov_action_id" era,
HuddleRule "committee_cold_credential" era, HuddleRule "epoch" era,
HuddleRule "unit_interval" era) =>
Proxy era -> Named Group
updateCommitteeGroup @DijkstraEra
instance HuddleGroup "new_constitution" DijkstraEra where
huddleGroup :: Proxy DijkstraEra -> Named Group
huddleGroup = forall era.
(HuddleRule "gov_action_id" era, HuddleRule "constitution" era) =>
Proxy era -> Named Group
newConstitutionGroup @DijkstraEra
instance HuddleRule "info_action" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Rule
infoActionRule
instance HuddleRule "gov_action" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleGroup "parameter_change_action" era,
HuddleGroup "hard_fork_initiation_action" era,
HuddleGroup "treasury_withdrawals_action" era,
HuddleGroup "no_confidence" era,
HuddleGroup "update_committee" era,
HuddleGroup "new_constitution" era,
HuddleRule "info_action" era) =>
Proxy era -> Rule
govActionRule @DijkstraEra
instance HuddleRule "proposal_procedure" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "coin" era, HuddleRule "reward_account" era,
HuddleRule "gov_action" era, HuddleRule "anchor" era) =>
Proxy era -> Rule
proposalProcedureRule @DijkstraEra
instance HuddleRule "proposal_procedures" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
HuddleRule "proposal_procedure" era =>
Proxy era -> Rule
proposalProceduresRule @DijkstraEra
instance HuddleRule "transaction_input" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
p =
Text
"transaction_input"
Text -> ArrayChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= ArrayChoice -> ArrayChoice
arr
[ Key
"transaction_id" Key -> Rule -> ArrayEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_id" Proxy DijkstraEra
p
, Key
"index" Key -> Constrained -> ArrayEntry
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))
]
instance HuddleRule "required_signers" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
p =
Text
"required_signers"
Text -> GRuleCall -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"addr_keyhash" Proxy DijkstraEra
p)
instance HuddleRule "value" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "policy_id" era, HuddleRule "asset_name" era,
HuddleRule "positive_coin" era) =>
Proxy era -> Rule
conwayValueRule @DijkstraEra
instance HuddleRule "mint" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "policy_id" era, HuddleRule "asset_name" era,
HuddleRule "nonzero_int64" era) =>
Proxy era -> Rule
conwayMintRule @DijkstraEra
instance HuddleRule "withdrawals" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. Era era => Proxy era -> Rule
conwayWithdrawalsRule @DijkstraEra
instance HuddleRule "data" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "plutus_data" era => Proxy era -> Rule
dataRule @DijkstraEra
instance HuddleRule "datum_option" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "hash32" era, HuddleRule "data" era) =>
Proxy era -> Rule
datumOptionRule @DijkstraEra
instance HuddleRule "alonzo_transaction_output" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "address" era, HuddleRule "value" era,
HuddleRule "hash32" era) =>
Proxy era -> Rule
alonzoTransactionOutputRule @DijkstraEra
instance HuddleRule "transaction_output" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 @"alonzo_transaction_output" Proxy DijkstraEra
p
Rule -> Rule -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Proxy DijkstraEra -> Rule -> Rule
forall era.
(HuddleRule "address" era, HuddleRule "value" era,
HuddleRule "datum_option" era) =>
Proxy era -> Rule -> Rule
babbageTransactionOutput Proxy DijkstraEra
p (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"script" Proxy DijkstraEra
p)
instance HuddleRule "potential_languages" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = Proxy DijkstraEra -> Rule
forall era. Proxy era -> Rule
potentialLanguagesRule
instance HuddleRule "redeemers" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
p =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|Dijkstra uses map format only for redeemers.
|The flat array format has been removed.
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"redeemers"
Text -> MapChoice -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= MapChoice -> MapChoice
mp
[ Word64
1
Word64 -> MapEntry -> MapEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ ArrayChoice -> Key
forall r. IsType0 r => r -> Key
asKey
( 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 DijkstraEra
p
, Key
"index" Key -> Constrained -> ArrayEntry
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))
]
)
Key -> ArrayChoice -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> ArrayChoice -> ArrayChoice
arr
[ 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 DijkstraEra
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 DijkstraEra
p
]
]
instance HuddleRule "script_data_hash" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 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 (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 cost_models 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.
|For PlutusV3 (language id 2), the language view is the following:
| - the value of cost_models map at key 2 is encoded as a definite length list.
|
|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.
|
|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):
|[ A0 | datums | A0 ]
|corresponding to a CBOR empty map and an empty map for language view.
|This empty redeeemer case has changed from the previous eras, since default
|representation for redeemers has been changed to a map. Also whenever redeemers are
|supplied either as a map or as an array they must contain at least one element,
|therefore there is no way to override this behavior by providing a custom
|representation for empty redeemers.
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Proxy DijkstraEra -> Rule
forall era. Era era => Proxy era -> Rule
scriptDataHashRule Proxy DijkstraEra
p
instance HuddleRule "transaction" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 "ex_unit_prices" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 @"nonnegative_interval" Proxy DijkstraEra
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 @"nonnegative_interval" Proxy DijkstraEra
p
]
instance HuddleRule "pool_voting_thresholds" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "unit_interval" era => Proxy era -> Rule
poolVotingThresholdsRule @DijkstraEra
instance HuddleRule "drep_voting_thresholds" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "unit_interval" era => Proxy era -> Rule
drepVotingThresholdsRule @DijkstraEra
instance HuddleRule "protocol_param_update" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 -> 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"minfeeA"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (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 @"coin" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"minfeeB"
, 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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 -> 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 value size"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
23 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
"collateral percentage"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
24 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 collateral inputs"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
25 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"pool_voting_thresholds" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"pool voting thresholds"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
26 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"drep_voting_thresholds" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"drep voting thresholds"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
27 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
"min committee size"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
28 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"committee term limit"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
29 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"goveranance action validity period"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
30 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"governance action deposit"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
31 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"drep deposit"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
32 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"drep inactivity period"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
33 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 DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"minfee refScript coins per byte"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
34 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 refScript size per block"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
35 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 refScript size per tx"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
36 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_word32" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"refScript cost stride"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
37 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_interval" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"refScript cost multiplier"
]
instance HuddleRule "proposed_protocol_parameter_updates" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "genesis_hash" era,
HuddleRule "protocol_param_update" era) =>
Proxy era -> Rule
proposedProtocolParameterUpdatesRule @DijkstraEra
instance HuddleRule "update" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
HuddleRule "proposed_protocol_parameter_updates" era =>
Proxy era -> Rule
updateRule @DijkstraEra
instance HuddleRule "header_body" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
p
, Key
"block_body_size" Key -> Constrained -> ArrayEntry
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))
, 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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
p
]
instance HuddleRule "header" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "header_body" era => Proxy era -> Rule
headerRule @DijkstraEra
instance HuddleRule "block" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
p)]
]
instance HuddleRule "auxiliary_scripts" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "native_script" era => Proxy era -> Rule
auxiliaryScriptsRule @DijkstraEra
instance HuddleRule "auxiliary_data_array" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era. HuddleRule "auxiliary_scripts" era => Proxy era -> Rule
auxiliaryDataArrayRule @DijkstraEra
instance HuddleRule "transaction_body" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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
maybeTaggedSet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"certificates" Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy DijkstraEra
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
==> Proxy DijkstraEra -> Rule
forall era.
(HuddleRule "addr_keyhash" era, HuddleRule "credential" era) =>
Proxy era -> Rule
guardsRule Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"guards (replaces required_signers)"
, 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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"transaction_input" Proxy DijkstraEra
p)) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"reference inputs"
, 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 @"voting_procedures" Proxy DijkstraEra
p)
, 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 @"proposal_procedures" Proxy DijkstraEra
p)
, 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 @"coin" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"current treasury value"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
22 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"positive_coin" Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"donation"
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
23 Key -> Rule -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Proxy DijkstraEra -> Rule
forall era.
(HuddleRule "transaction_input" era,
HuddleRule "transaction_output" era, HuddleRule "slot" era,
HuddleRule "certificates" era, HuddleRule "withdrawals" era,
HuddleRule "auxiliary_data_hash" era, HuddleRule "mint" era,
HuddleRule "script_data_hash" era, HuddleRule "network_id" era,
HuddleRule "voting_procedures" era,
HuddleRule "proposal_procedures" era, HuddleRule "coin" era,
HuddleRule "positive_coin" era, HuddleRule "credential" era,
HuddleRule "plutus_data" era,
HuddleRule "transaction_witness_set" era,
HuddleRule "auxiliary_data" era) =>
Proxy era -> Rule
subTransactionsRule Proxy DijkstraEra
p) MapEntry -> Comment -> MapEntry
forall a. HasComment a => a -> Comment -> a
//- Comment
"sub-transactions (NEW)"
]
instance HuddleRule "transaction_witness_set" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"vkeywitness" Proxy DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"native_script" Proxy DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"bootstrap_witness" Proxy DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v1_script" Proxy DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_data" Proxy DijkstraEra
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 DijkstraEra
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 -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v2_script" Proxy DijkstraEra
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
7 Key -> GRuleCall -> MapEntry
forall a me. (IsType0 a, IsEntryLike me) => Key -> a -> me
==> Rule -> GRuleCall
forall a. IsType0 a => a -> GRuleCall
maybeTaggedNonemptySet (forall (name :: Symbol) era.
HuddleRule name era =>
Proxy era -> Rule
huddleRule @"plutus_v3_script" Proxy DijkstraEra
p)
]
instance HuddleRule "native_script" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> 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,
HuddleRule "credential" era) =>
Proxy era -> Rule
dijkstraNativeScriptRule @DijkstraEra
instance HuddleRule "script" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule = forall era.
(HuddleRule "native_script" era, HuddleRule "plutus_v1_script" era,
HuddleRule "plutus_v2_script" era,
HuddleRule "plutus_v3_script" era,
HuddleRule "plutus_v4_script" era) =>
Proxy era -> Rule
dijkstraScriptRule @DijkstraEra
instance HuddleRule "redeemer_tag" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ = Proxy DijkstraEra -> Rule
forall era. Proxy era -> Rule
dijkstraRedeemerTagRule (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @DijkstraEra)
instance (Era era, HuddleRule "distinct_bytes" era) => HuddleRule "plutus_v4_script" era where
huddleRule :: Proxy era -> Rule
huddleRule Proxy era
p =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|Dijkstra introduces Plutus V4.
|
|Note: distinct VBytes ensures uniqueness in test generation.
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"plutus_v4_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 era
p
instance HuddleRule "auxiliary_data" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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
| Dijkstra adds plutus_v4_script support at index 5
|]
(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 DijkstraEra
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 DijkstraEra
p
Choice Type2 -> Rule -> Choice Type2
forall a c b.
(IsChoosable a c, IsChoosable b c) =>
a -> b -> Choice c
/ Proxy DijkstraEra -> Rule
forall era.
(HuddleRule "metadata" era, HuddleRule "native_script" era,
HuddleRule "plutus_v1_script" era,
HuddleRule "plutus_v2_script" era,
HuddleRule "plutus_v3_script" era,
HuddleRule "plutus_v4_script" era) =>
Proxy era -> Rule
auxiliaryDataMapRule Proxy DijkstraEra
p
instance HuddleRule "auxiliary_data_map" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
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 DijkstraEra
p)])
, 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 @"plutus_v3_script" Proxy DijkstraEra
p)])
, MapEntry -> MapEntry
forall a. CanQuantify a => a -> a
opt (Word64 -> Key
idx Word64
5 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_v4_script" Proxy DijkstraEra
p)])
]
)
instance HuddleRule "language" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
_ =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|0: Plutus v1
|1: Plutus v2
|2: Plutus v3
|3: Plutus v4 (NEW)
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ Text
"language" Text -> Ranged -> Rule
forall a. IsType0 a => Text -> a -> Rule
=:= (Integer
0 :: Integer) Integer -> Integer -> Ranged
forall a b. (IsRangeBound a, IsRangeBound b) => a -> b -> Ranged
... (Integer
3 :: Integer)
instance HuddleRule "cost_models" DijkstraEra where
huddleRule :: Proxy DijkstraEra -> Rule
huddleRule Proxy DijkstraEra
p =
Text -> Rule -> Rule
forall a. HasField' "description" a (Maybe Text) => Text -> a -> a
comment
Text
[str|The format for cost_models is flexible enough to allow adding
|Plutus built-ins and language versions in the future.
|
|Plutus v1: only 166 integers are used, but more are accepted (and ignored)
|Plutus v2: only 175 integers are used, but more are accepted (and ignored)
|Plutus v3: only 223 integers are used, but more are accepted (and ignored)
|Plutus v4: TBD integers are used (NEW)
|
|Any 8-bit unsigned number can be used as a key.
|]
(Rule -> Rule) -> Rule -> Rule
forall a b. (a -> b) -> a -> b
$ 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
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 @"int64" Proxy DijkstraEra
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 @"int64" Proxy DijkstraEra
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 @"int64" Proxy DijkstraEra
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 @"int64" Proxy DijkstraEra
p)]
, Word64
0 Word64 -> MapEntry -> MapEntry
forall a. CanQuantify a => Word64 -> a -> a
<+ Ranged -> Key
forall r. IsType0 r => r -> Key
asKey ((Integer
4 :: Integer) Integer -> Integer -> Ranged
forall a b. (IsRangeBound a, IsRangeBound b) => a -> b -> Ranged
... (Integer
255 :: Integer)) 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 @"int64" Proxy DijkstraEra
p)]
]