{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Cardano.Ledger.Plutus.Examples (
alwaysSucceedsNoDatum,
alwaysSucceedsWithDatum,
alwaysFailsNoDatum,
alwaysFailsWithDatum,
redeemerSameAsDatum,
evenDatum,
evenRedeemerNoDatum,
evenRedeemerWithDatum,
purposeIsWellformedNoDatum,
purposeIsWellformedWithDatum,
datumIsWellformed,
inputsOutputsAreNotEmptyNoDatum,
inputsOutputsAreNotEmptyWithDatum,
inputsOverlapsWithRefInputs,
) where
import Cardano.Ledger.Plutus.Language (Plutus (..), PlutusBinary (..), SLanguage (..))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as Base16 (decode)
import qualified Data.ByteString.Short as SBS (toShort)
import GHC.Stack
decodeHexPlutus :: HasCallStack => ByteString -> Plutus l
decodeHexPlutus :: forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus = ([Char] -> Plutus l)
-> (ByteString -> Plutus l) -> Either [Char] ByteString -> Plutus l
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Char] -> Plutus l
forall a. HasCallStack => [Char] -> a
error (PlutusBinary -> Plutus l
forall (l :: Language). PlutusBinary -> Plutus l
Plutus (PlutusBinary -> Plutus l)
-> (ByteString -> PlutusBinary) -> ByteString -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> PlutusBinary
PlutusBinary (ShortByteString -> PlutusBinary)
-> (ByteString -> ShortByteString) -> ByteString -> PlutusBinary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
SBS.toShort) (Either [Char] ByteString -> Plutus l)
-> (ByteString -> Either [Char] ByteString)
-> ByteString
-> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either [Char] ByteString
Base16.decode
alwaysSucceedsNoDatum :: SLanguage l -> Plutus l
alwaysSucceedsNoDatum :: forall (l :: Language). SLanguage l -> Plutus l
alwaysSucceedsNoDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"582701000022533333573466e1d200235573a6ea8d5d09aba235573c6ea80048800888004584480041"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"582701000022533333573466e1d200235573a6ea8d5d09aba235573c6ea80048800888004584480041"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"588f01010025329325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e1d"
, ByteString
"200000218009aba100109802a481035054310035573c0046aae74004dd51aba1357446aae78006430028c00030"
, ByteString
"003755264650013574200535742003357426ae880046ae88004d55cf1baa002911000a29344c00524103505435"
, ByteString
"00119319ab9c00180001"
]
alwaysSucceedsWithDatum :: SLanguage l -> Plutus l
alwaysSucceedsWithDatum :: forall (l :: Language). SLanguage l -> Plutus l
alwaysSucceedsWithDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"582c010000222533333573466e1d200235573a6ea8d5d09aba235573c6ea800488008880044480044c8d400400"
, ByteString
"59"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"582c010000222533333573466e1d200235573a6ea8d5d09aba235573c6ea800488008880044480044c8d400400"
, ByteString
"59"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"588f01010025329325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e1d"
, ByteString
"200000218009aba100109802a481035054310035573c0046aae74004dd51aba1357446aae78006430008c00830"
, ByteString
"023755264650013574200535742003357426ae880046ae88004d55cf1baa002911000a29344c00524103505435"
, ByteString
"00119319ab9c00180001"
]
alwaysFailsNoDatum :: SLanguage l -> Plutus l
alwaysFailsNoDatum :: forall (l :: Language). SLanguage l -> Plutus l
alwaysFailsNoDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"582701000022533333573466e1d200235573a6ea8d5d09aba235573c6ea80048800888004448004581"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"582701000022533333573466e1d200235573a6ea8d5d09aba235573c6ea80048800888004448004581"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"587d01010025329325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e1d"
, ByteString
"200000218009aba100109802a481035054310035573c0046aae74004dd51aba1357446aae78006430008c00830"
, ByteString
"0237546ae84d5d11aba235573c6ea800a29344c00524010350543500119319ab9c00180001"
]
alwaysFailsWithDatum :: SLanguage l -> Plutus l
alwaysFailsWithDatum :: forall (l :: Language). SLanguage l -> Plutus l
alwaysFailsWithDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"5827010000222533333573466e1d200235573a6ea8d5d09aba235573c6ea8004880088800458448005"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"5827010000222533333573466e1d200235573a6ea8d5d09aba235573c6ea8004880088800458448005"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"587d01010025329325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e1d"
, ByteString
"200000218009aba100109802a481035054310035573c0046aae74004dd51aba1357446aae78006430028c00030"
, ByteString
"0037546ae84d5d11aba235573c6ea800a29344c00524010350543500119319ab9c00180001"
]
redeemerSameAsDatum :: SLanguage l -> Plutus l
redeemerSameAsDatum :: forall (l :: Language). SLanguage l -> Plutus l
redeemerSameAsDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"584201000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19ba"
, ByteString
"f004005002001112001161220021220011323500100161"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"584201000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19ba"
, ByteString
"f004005002001112001161220021220011323500100161"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"588c0101002532932325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e"
, ByteString
"1d200000218009aba1001098032481035054310035573c0046aae74004dd51aba1357446aae7800642666ae68c"
, ByteString
"dd78009aba1003800400a30020c008dd51aba1357440026ae88d55cf1baa0028a4d13001490103505435001193"
, ByteString
"19ab9c00180001"
]
evenDatum :: SLanguage l -> Plutus l
evenDatum :: forall (l :: Language). SLanguage l -> Plutus l
evenDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"584901000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19b8"
, ByteString
"748000cdc31bad00548010008004448004584880084880044c8d40040059"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"584901000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19b8"
, ByteString
"748000cdc31bad00548010008004448004584880084880044c8d40040059"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"589501010025329325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e1d"
, ByteString
"200000218009aba100109802a481035054310035573c0046aae74004dd51aba1357446aae7800642666ae68cdc"
, ByteString
"3a400066e18dd6800a400900080144ca400600260994800c004c6ea8d5d09aba2357446aae78dd500145268980"
, ByteString
"0a490350543500119319ab9c00180001"
]
evenRedeemerNoDatum :: SLanguage l -> Plutus l
evenRedeemerNoDatum :: forall (l :: Language). SLanguage l -> Plutus l
evenRedeemerNoDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"58440100002253322335333573466e1d200235573a6ea8d5d09aba235573c6ea800c0080045854cd4ccd5cd19b"
, ByteString
"8748000cdc31bad00448010008004448004584880084880041"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"58440100002253322335333573466e1d200235573a6ea8d5d09aba235573c6ea800c0080045854cd4ccd5cd19b"
, ByteString
"8748000cdc31bad00448010008004448004584880084880041"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"5899010100253293232532333573466e1d200235573a0042b2646464a666ae68cdc3a400400430021533357346"
, ByteString
"6e1d200000218009aba100109803a481035054310035573c0046aae74004dd51aba1357446aae7800a43002898"
, ByteString
"00a4c130014988ccd5cd19b8748000cdc31bad35742006900240020046ea8d5d09aba2001357446aae78dd5001"
, ByteString
"452689800a490350543500119319ab9c00180001"
]
evenRedeemerWithDatum :: SLanguage l -> Plutus l
evenRedeemerWithDatum :: forall (l :: Language). SLanguage l -> Plutus l
evenRedeemerWithDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"584901000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19b8"
, ByteString
"748000cdc31bad00448010008004448004584880084880044c8d40040059"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"584901000022253332235333573466e1d200235573a6ea8d5d09aba235573c6ea800c00800454cd4ccd5cd19b8"
, ByteString
"748000cdc31bad00448010008004448004584880084880044c8d40040059"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"58930101002532932325333573466e1d200235573a0022b2646464a666ae68cdc3a4004004300215333573466e"
, ByteString
"1d200000218009aba1001098032481035054310035573c0046aae74004dd51aba1357446aae7800642666ae68c"
, ByteString
"dc3a400066e18dd69aba1003480120010028c008300237546ae84d5d10009aba235573c6ea800a29344c005241"
, ByteString
"0350543500119319ab9c00180001"
]
purposeIsWellformedNoDatum :: SLanguage l -> Plutus l
purposeIsWellformedNoDatum :: forall (l :: Language). SLanguage l -> Plutus l
purposeIsWellformedNoDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"59058f01000022323232532323322323232335333573466e1d2000001005004153353323001001233003005253"
, ByteString
"35333573466ebcdd49bae357426aae78028d55ce80080380309004091980180180099980180491111111110039"
, ByteString
"308038b0a99a999ab9a3370e90010008028020b0a99191919a999ab9a3370e90020020040038a99a9801999980"
, ByteString
"11191919299a999ab9a3370e90000010060058999109198008018011aba1001375a6ae84d5d100089806a48103"
, ByteString
"5054310035573c0046aae74004dd500091a8009119ba548000cd5d000119aba0375000297ae0233002357426aa"
, ByteString
"e78030d400488008ccc01803088888888880149858402854cd4ccd5cd19b874801801002001c54cd4c00ccccc0"
, ByteString
"08800480048c8c94c8cd4ccd5cd19b8748000d55ce801006005899299a999ab9a3370e90001aab9d00100d00c1"
, ByteString
"33006357426aae7800cd5d09aab9e00113002498dd500209800a4c4a6466a666ae68cdc3a40046aae7400c0340"
, ByteString
"304c94cd4ccd5cd19b8748008d55ce8008070068998039aba135573c0086ae84d55cf0008980124c6ea80144c0"
, ByteString
"052623232332330010072233300300a2253353300d004002133007003001101323005498888c94cd4ccd5cd19b"
, ByteString
"8748010d55ce800809809099198021aba1001375c6ae84d5d10009aab9e00113002498dd50019180124c464664"
, ByteString
"660020104466600601644a66a666ae68cdc780200100a80a099804001800880a11802a4c44464a66a666ae68cd"
, ByteString
"c3a400c6aae7400405004c4c8cc010dd71aba1001375c6ae84d5d10009aab9e00113002498dd50019180124c46"
, ByteString
"4664660020124466600601844a66a666ae68cdc780200100b00a8999ab9a3370e00600202c02a202a4600a9311"
, ByteString
"119299a999ab9a3370e90041aab9d00101501413233004375c6ae84004dd69aba1357440026aae780044c00926"
, ByteString
"37540064600493129919a999ab9a3370e90051aab9d00801201115335333573466e1d200a35573a6ea80280480"
, ByteString
"4440484c005261300149894cd4ccd5cd19b8748030d55ce8040090088999ab9a3370e90061aab9d37540140240"
, ByteString
"22202244666ae68cdc78010008078071baa001357426aae78030ccc0180308888888888018985840284c8d4004"
, ByteString
"005888c94c8cd4ccd5cd19b8748000d55ce801005805099299a999ab9a3370e90001aab9d00100c00b13232532"
, ByteString
"335333573466e1d200035573a00401e01c264a66a666ae68cdc3a40006aae7400404003c4ccd5cd19b8f375c6a"
, ByteString
"e84d55cf0019bae357426aae7800404003c4c00926375400626002931299a999ab9a3370e90011aab9d00200f0"
, ByteString
"0e1325335333573466e1d200235573a00202001e2666ae68cdc79bae357426aae7800cdd71aba135573c002020"
, ByteString
"01e201e6ea800c4038dd51aba135573c0086ae84d55cf0008980124c6ea800c4c0052623323300100522233300"
, ByteString
"40072225335333573466e1c01800c04804454cd4ccd5cd19b870050020120111333573466e1c01000404804440"
, ByteString
"444044803c888c94cd4ccd5cd19b8748008d55ce800807807099191998029bad357420046eb4d5d08009bad357"
, ByteString
"426ae88004d5d10009aab9e00113002498dd500190059baa0022223223002001323001001223330084bd701119"
, ByteString
"299a980300089919aba03008002001330050050021330050050023007002001233357346ae8c004018014d55ce"
, ByteString
"8039112999aab9f0011003133002357420026ae88004888c8c8c8c8c8c8c8c8c8cccccccccc02cdd61aba10093"
, ByteString
"7586ae84020dd59aba100737566ae84018dd61aba100537586ae84010d5d08019bac357420046eb0d5d0800991"
, ByteString
"919299a999ab9a3370e900000100880809bae35742002260249201035054310035573c0046aae74004dd51aba1"
, ByteString
"357440026ae88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026aae78dd500189100109"
, ByteString
"1000919319ab9c0010021200137546ae84d5d10011aba100135573c6ea8005"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"59053501000022323232532332232323232335333573466e1d2000001006005153353330027526eb8d5d09aab9"
, ByteString
"e0083330040092222222222220082610071615335333573466e1d20020010060051615335333573466e1d20040"
, ByteString
"01006005153353330022001357426aae78020ccc01002488888888888801898401c584c8c8c8c8c8c94cd4ccd5"
, ByteString
"cd19b874801801c03002c54cd4ccd5cd1aba3300133300a00f2222222222220072600c00b16100d13235001001"
, ByteString
"63230010012233300a4bd7011299a991929919a999ab9a3370e90001aab9d0020120111325335333573466e1d2"
, ByteString
"00035573a0020260242660126ae84d55cf0019aba135573c00226004931baa0051300149894c8cd4ccd5cd19b8"
, ByteString
"748008d55ce801809809099299a999ab9a3370e90011aab9d00101401313300a357426aae78010d5d09aab9e00"
, ByteString
"113002498dd500309800a4c46466601600a4466601a01244a66a6601c008004266024006002202e46008931180"
, ByteString
"124c46466601a00c4466601e01444a66a666ae68cdc780200100c80c099809801800880c1180224c4600493119"
, ByteString
"1998078039119980880591299a999ab9a3371e0080040340322666ae68cdc380180080d00c880c9180224c4600"
, ByteString
"493129919a999ab9a3370e90051aab9d00701701615335333573466e1d200a35573a6ea802805c058405c4c005"
, ByteString
"261300149894cd4ccd5cd19b8748030d55ce80380b80b0999ab9a3370e90061aab9d375401402e02c202c6ea80"
, ByteString
"04d5d09aab9e0111335740004660080080022660080080020024464a6466a666ae68cdc3a40006aae740080380"
, ByteString
"344c94cd4ccd5cd19b8748000d55ce8008078070991929919a999ab9a3370e90001aab9d002012011132533533"
, ByteString
"3573466e1d200035573a0020260242666ae68cdc79bae357426aae7800cdd71aba135573c00202602426004931"
, ByteString
"baa0031300149894cd4ccd5cd19b8748008d55ce801009008899299a999ab9a3370e90011aab9d001013012133"
, ByteString
"3573466e3cdd71aba135573c0066eb8d5d09aab9e0010130121012375400620226ea8d5d09aab9e004357426aa"
, ByteString
"e780044c0092637540062600293119919800802911199802003911299a999ab9a3370e00c00602a0282a66a666"
, ByteString
"ae68cdc380280100a80a0999ab9a3370e00800202a02820282028402444464a66a666ae68cdc3a40046aae7400"
, ByteString
"40480444c8c8ccc014dd69aba1002375a6ae84004dd69aba1357440026ae88004d55cf0008980124c6ea800c80"
, ByteString
"38dd500111119299a999ab9a3370e90021aab9d00100d00c13233004357420026eb8d5d09aba200135573c0022"
, ByteString
"6004931baa003222325335333573466e1d200635573a002018016264660086eb8d5d08009bae357426ae88004d"
, ByteString
"55cf0008980124c6ea800c888c94cd4ccd5cd19b8748020d55ce800805805099198021bae357420026eb4d5d09"
, ByteString
"aba200135573c00226004931baa00322333573466e3c00800402001cd55ce80391119918008009198028039299"
, ByteString
"a999ab9a3375e600a0086aae740040240204802848cc00c00c0040048894ccd55cf80088018998011aba100135"
, ByteString
"744002444646464646464646464646466666666666601a6eb0d5d08059bac357420146eb0d5d08049bab357420"
, ByteString
"106eacd5d08039bac3574200c6eacd5d08029aba100437586ae8400cdd59aba100237566ae84004c8c8c94cd4c"
, ByteString
"cd5cd19b874800000804c0484dd71aba100113263357389201035054310001435573c0046aae74004dd51aba13"
, ByteString
"57440026ae88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aab9e"
, ByteString
"3754006244004244002240026ea8d5d09aba2002357420026aae78dd500081"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"590830010100323232323232322532932323232323253232333573466e1d200000113330027526eb8d5d09aab9"
, ByteString
"e00333300c75246e98004c02cccc041d711bab00137566ae8401854c8c8c8c8ccd5cd19b87480080144c964cc0"
, ByteString
"0800cd5d09aba200190c00a2600a6666008006400246464a666ae68c8cdc79800801180080191bae357426aae7"
, ByteString
"8dd50008999ab9a323370e6002004600200646eb4d5d09aba235573c6ea800600100218011aba1003357426aae"
, ByteString
"78dd50009bac3574201835573c00e2a666ae68cdc3a400800a266600c40026ae84d55cf0039bab357420102a66"
, ByteString
"6ae68cdc3a400c00a264600a666600800640024646464664660020084466600600e44b26600e00800515900390"
, ByteString
"ac801484ccd5cd19b87002001800400a30024564006430028c0008c0084600a93111192999ab9a3370e90001aa"
, ByteString
"b9d001132330043574200266016eb4d5d09aba200135573c00226004931baa003230024988c8cc8cc00401488c"
, ByteString
"cc00c0208964cc02001000a2b2007215900290999ab9a3370e004003000801460048ac800c8600518001180108"
, ByteString
"c01526222325333573466e1d200235573a002264660086ae84004cc031d69aba1357440026aae780044c009263"
, ByteString
"7540064600493119191991980080391199801805112c9980500200144cc01c00c006300211802a4c44464a666a"
, ByteString
"e68cdc3a40086aae740044c8cc010d5d08009aba1357440026aae780044c009263754006460049311919919800"
, ByteString
"8041111998020061112c99806803001c564cc02801400a2666ae68cdc3802000c0020051801230021180324c44"
, ByteString
"464a666ae68cdc3a400c6aae740044c8c8ccc014d5d08011aba1001375a6ae84d5d10009aba200135573c00226"
, ByteString
"004931baa003230024988c8cc8cc00402488ccc00c0308964cc03001000a2666ae68cdc3801800c00200518010"
, ByteString
"8c01526222325333573466e1d200835573a002264660086ae84004dd69aba1357440026aae780044c009263754"
, ByteString
"0064600493119299199ab9a3370e90051aab9d0021325333573466e1d200a35573a0022660146ae84d55cf0019"
, ByteString
"aba135573c00226004931baa00b130014988c8cc8cc00403088ccc00c03c8964cc03c01000a2666ae68cdc3801"
, ByteString
"800c002005180108c01526222325333573466e1d200c35573a002264660086ae84004dd69aba1357440026aae7"
, ByteString
"80044c00926375400646004931191991980080691199801808112c9980800200144cc04000c006300211802a4c"
, ByteString
"44464a666ae68cdc3a40246aae740044c8cc010d5d08009aba1357440026aae780044c00926375400646004931"
, ByteString
"2999ab9a3370e900a1aab9d0041325333573466e1d201435573a0022660186ae84d55cf0029aba135573c00230"
, ByteString
"02375401a300237540104464a64666ae68cdc3a40006aae740084c94ccd5cd19b8748000d55ce8008999ab9a33"
, ByteString
"71e6eb8d5d09aab9e003375c6ae84d55cf000c00200426004931baa0031300149894c8c8ccd5cd19b8748008d5"
, ByteString
"5ce8020992999ab9a3370e90011aab9d001133003357426aae78014d5d09aab9e00113002498dd500289800a4c"
, ByteString
"46646600200e4466600601044a666ae68cdc78020010998038018008c008a00444464a666ae68cdc3a40086aae"
, ByteString
"740044c8cc010dd71aba1001357426ae88004d55cf0008980124c6ea800ca0044464a64666ae68cdc3a40006aa"
, ByteString
"e740084c94ccd5cd19b8748000d55ce8008998061aba135573c0066ae84d55cf0008980124c6ea800c4c005262"
, ByteString
"532333573466e1d200235573a0062a666ae68cdc3a40046aae74dd50020c0004c005261300149894ccd5cd19b8"
, ByteString
"748010d55ce8018999ab9a3370e90021aab9d37540090008010c008dd50011baa0022232532333573466e1d200"
, ByteString
"035573a004264a666ae68cdc3a40006aae740044ccd5cd19b8f375c6ae84d55cf0019bae357426aae780060010"
, ByteString
"0213002498dd500189800a4c4a666ae68cdc3a40046aae740084c94ccd5cd19b8748008d55ce8008999ab9a337"
, ByteString
"1e6eb8d5d09aab9e003375c6ae84d55cf000c00200430023754006300237540046ae84d5d10011bac357420146"
, ByteString
"aae7801c54ccd5cd19b87480200144ccc0188004d5d09aab9e00737566ae84d5d11aba2357446ae88d5d11aba2"
, ByteString
"00815333573466e1d200a0051328001aab9e00713290018009888c8c8c94ccd5cd19b874800800860042a666ae"
, ByteString
"68cdc3a4000004300130053574200213011491035054310035573c0046aae74004dd5000900091119118010009"
, ByteString
"918008009119980ba5eb8088c964c01800626466ae80c020008004cc01401400a26600a00a0043007002001233"
, ByteString
"357346ae8c00600100235573a00444466460020024660270022333573466ebcc014010d55ce800940008cc00c0"
, ByteString
"0c004004dd51aba1357446ae88014d5d10009aba2001357446ae88d5d11aba200135573c6ea8d5d08009aab9e3"
, ByteString
"754005149a260029210350543500119319ab9c001800191800800912c800c6001221900291192c9980594800c8"
, ByteString
"c88c008c038004c8c00400489640063000910c00e00200b0024cc010010004000c4cc01c01c012443003800802"
, ByteString
"cccc029d491ba80013300d29001919118011808000991800800912c800c6001221801c00401600499802002000"
, ByteString
"80034cc02402401833300b75ceb4004223223005300200132300100122590018c0024430039002914004c02000"
, ByteString
"a600e0024cc010010004323001001229001a5eb7bdb1824466ae82400a4466ec00080046600800800225333573"
, ByteString
"466e24005200018000c00c00700011911801000991800800912c800c600122132332300100122590018801c886"
, ByteString
"006005330040040010c01800ccc010010004444664600200246600b00022801c004c018d55ce8014c014d55cf0"
, ByteString
"0126600600600200122253335573e00220062660046ae84004d5d10009"
]
purposeIsWellformedWithDatum :: SLanguage l -> Plutus l
purposeIsWellformedWithDatum :: forall (l :: Language). SLanguage l -> Plutus l
purposeIsWellformedWithDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"58fa01000022232323232332232325335333573466e1d200235573a00e0080062a66a666ae68d5d198009bac35"
, ByteString
"7426aae78dd51aba1008004003161005163230010012253335573e002297ae013322533532325335333573466e"
, ByteString
"3cc01c004c01c0080240204ccd5cd19b87300b001300b0020090081008357426aae7802cd5d09aab9e37540042"
, ByteString
"66ae80008cc0100100044cc010010004d5d08009aba200123232325335333573466e1d20000020060051375c6a"
, ByteString
"e840044c98cd5ce249035054310000735573c0046aae74004dd51aba135573c6ea8004488008488004480048dd"
, ByteString
"69aba1357446aae78dd50009baa357426ae88004d55cf1baa00101"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"58fa01000022232323232332232325335333573466e1d200235573a00e0080062a66a666ae68d5d198009bac35"
, ByteString
"7426aae78dd51aba1008004003161005163230010012253335573e002297ae013322533532325335333573466e"
, ByteString
"3cc01c004c01c0080240204ccd5cd19b87300b001300b0020090081008357426aae7802cd5d09aab9e37540042"
, ByteString
"66ae80008cc0100100044cc010010004d5d08009aba200123232325335333573466e1d20000020060051375c6a"
, ByteString
"e840044c98cd5ce249035054310000735573c0046aae74004dd51aba135573c6ea8004488008488004480048dd"
, ByteString
"69aba1357446aae78dd50009baa357426ae88004d55cf1baa00101"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"59010c0101002532932325333573466e1d200235573a002264646464b2646464a666ae68cdc3a4004004300215"
, ByteString
"333573466e1d200000218009aba1001098052481035054310035573c0046aae74004dd51aba135744009213335"
, ByteString
"7346ae8cc008dd61aba135573c6ea8d5d0803c00a00118010c8c004004894ccd55cf8008a5eb804cc8964c8c94"
, ByteString
"ccd5cd19b8f300700130070021333573466e1cc020004c02000a00100218011aba1008357426aae78dd500144c"
, ByteString
"d5d000119802002000c4cc0100100046ae84004d5d100091bae357426aae78dd500091bad357426ae88d55cf1b"
, ByteString
"aa00135573c002300237546ae84d5d11aba200135573c6ea800a29344c0052410350543500119319ab9c001800"
, ByteString
"01"
]
datumIsWellformed :: SLanguage l -> Plutus l
datumIsWellformed :: forall (l :: Language). SLanguage l -> Plutus l
datumIsWellformed =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"58ee010000222325323332235333573466e1d200235573a6ea8d5d09aba20040020011533533357346ae8ccc8c"
, ByteString
"004004894ccd55cf8008a5eb804c8c94cd4ccd5cd19baf00b30012200100600513233574060044466e95200033"
, ByteString
"57406ea4008cd5d0000a5eb80004cc0100100084cc0100100094c8c8c94cd4ccd5cd19b874800000802001c4cc"
, ByteString
"8848cc00400c008dd71aba1001357426ae880044c98cd5ce2481035054310000935573c0046aae74004dd51aba"
, ByteString
"1002357440026eb0d5d09aba2357446ae88d5d11aba2357446ae88d5d11aab9e37546ae8401000800458400c48"
, ByteString
"80084880045848004d55cf1baa0011"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"58bd01000023322323222325335333573466e1d200235573a6ea8d5d09aba20010070061533533357346ae8cc0"
, ByteString
"10cc8c0040048cc0192f5c04466ae80d55cf001198018018009bab357426ae88d5d11aba2357446ae88d5d11ab"
, ByteString
"a2357446ae88d5d11aab9e37546ae8400401c0185844800458d55cf1baa001323001001223330034bd7011299a"
, ByteString
"999ab9a3375e01000400e00c266ae80008cc0100100044cc0100100040048894ccd55cf80088018998011aba10"
, ByteString
"0135744002244004244003"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"5901030101002532932325333573466e1d200235573a0022b2646464a666ae68cdc3a400400430021533357346"
, ByteString
"6e1d200000218009aba1001098032481035054310035573c0046aae74004dd51aba1357446aae7800646464266"
, ByteString
"6ae68d5d198009991800800919801a5eb8088cd5d01aab9e0023300300300137566ae84d5d11aba2357446ae88"
, ByteString
"d5d11aba2357446ae88d5d11aba235573c6ea8d5d0802c00a0006460020024466600697ae0225333573466ebc0"
, ByteString
"180084cd5d0001198020020008998020020008009112999aab9f0011003133002357420026ae8800630020c008"
, ByteString
"dd51aba1357446ae88004d55cf1baa0028a4d1300149010350543500119319ab9c00180001"
]
inputsOutputsAreNotEmptyNoDatum :: SLanguage l -> Plutus l
inputsOutputsAreNotEmptyNoDatum :: forall (l :: Language). SLanguage l -> Plutus l
inputsOutputsAreNotEmptyNoDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"58e301000022532335332253232335300233001222222222200a26100413002330012222222222009262232323"
, ByteString
"2323232323232333333333300b37586ae84024dd61aba100837566ae8401cdd59aba100637586ae84014dd61ab"
, ByteString
"a1004357420066eb0d5d08011bac35742002646464a66a666ae68cdc3a400000402202026eb8d5d0800899319a"
, ByteString
"b9c491035054310001235573c0046aae74004dd51aba1357440026ae88004d5d10009aba2001357440026ae880"
, ByteString
"04d5d10009aba2001357440026aae78dd51aba135573c6ea801c8ccd5cd1aba300100300212200212200116100"
, ByteString
"11200101"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"58fb0100002253233533225323233530023300122222222222200c261004130023300122222222222200a26223"
, ByteString
"23232323232323232323233333333333300d37586ae8402cdd61aba100a37586ae84024dd59aba100837566ae8"
, ByteString
"401cdd61aba100637566ae84014d5d08021bac357420066eacd5d08011bab35742002646464a66a666ae68cdc3"
, ByteString
"a400000402602426eb8d5d0800899319ab9c4901035054310001435573c0046aae74004dd51aba1357440026ae"
, ByteString
"88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aab9e37546ae84d"
, ByteString
"55cf1baa007233357346ae8c00400c00848800848800458400448005"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"58d601010025329323253232333573466e1d200235573a006264b26600640026ae84d5d1000c86005130024986"
, ByteString
"aae7800c4c0052625953293001323237586ae84008c011d69aab9e37546ae8401630008980099191bac3574200"
, ByteString
"46008eb4d5d11aba235573c6ea8d5d080288ccd5cd1aba3001800400a30028c00044646464a666ae68cdc3a400"
, ByteString
"4004300215333573466e1d2000002180098029aba1001098042481035054310035573c0046aae74004dd50009b"
, ByteString
"aa357426ae88d5d10009aab9e3754005149a260029210350543500119319ab9c00180001"
]
inputsOutputsAreNotEmptyWithDatum :: SLanguage l -> Plutus l
inputsOutputsAreNotEmptyWithDatum :: forall (l :: Language). SLanguage l -> Plutus l
inputsOutputsAreNotEmptyWithDatum =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 ->
[ ByteString
"58e4010000222532335332253232335300233001222222222200a2610041300233001222222222200926223232"
, ByteString
"32323232323232333333333300b37586ae84024dd61aba100837566ae8401cdd59aba100637586ae84014dd61a"
, ByteString
"ba1004357420066eb0d5d08011bac35742002646464a66a666ae68cdc3a400000402202026eb8d5d0800899319"
, ByteString
"ab9c4901035054310001235573c0046aae74004dd51aba1357440026ae88004d5d10009aba2001357440026ae8"
, ByteString
"8004d5d10009aba2001357440026aae78dd51aba135573c6ea801c8ccd5cd1aba3001003002122002122001161"
, ByteString
"0011200101"
]
SLanguage l
SPlutusV2 ->
[ ByteString
"58fb01000022253233533225323233530023300122222222222200c261004130023300122222222222200a2622"
, ByteString
"323232323232323232323233333333333300d37586ae8402cdd61aba100a37586ae84024dd59aba100837566ae"
, ByteString
"8401cdd61aba100637566ae84014d5d08021bac357420066eacd5d08011bab35742002646464a66a666ae68cdc"
, ByteString
"3a400000402602426eb8d5d0800899319ab9c491035054310001435573c0046aae74004dd51aba1357440026ae"
, ByteString
"88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aab9e37546ae84d"
, ByteString
"55cf1baa007233357346ae8c00400c00848800848800458400448005"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"58d601010025329323253232333573466e1d200235573a006264b26600640026ae84d5d1000c84c00d268c0086"
, ByteString
"aae7800c4c0052625953293001323237586ae84008c011d69aab9e37546ae8401630008980099191bac3574200"
, ByteString
"46008eb4d5d11aba235573c6ea8d5d080288ccd5cd1aba3001800400a30028c00044646464a666ae68cdc3a400"
, ByteString
"4004300215333573466e1d2000002180098029aba1001098042481035054310035573c0046aae74004dd50009b"
, ByteString
"aa357426ae88d5d10009aab9e3754005149a260029210350543500119319ab9c00180001"
]
inputsOverlapsWithRefInputs :: SLanguage l -> Plutus l
inputsOverlapsWithRefInputs :: forall (l :: Language). SLanguage l -> Plutus l
inputsOverlapsWithRefInputs =
ByteString -> Plutus l
forall (l :: Language). HasCallStack => ByteString -> Plutus l
decodeHexPlutus (ByteString -> Plutus l)
-> (SLanguage l -> ByteString) -> SLanguage l -> Plutus l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString)
-> (SLanguage l -> [ByteString]) -> SLanguage l -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
SLanguage l
SPlutusV1 -> [Char] -> [ByteString]
forall a. HasCallStack => [Char] -> a
error [Char]
"Script not available in PlutusV1"
SLanguage l
SPlutusV2 ->
[ ByteString
"590666010000323232323322323232323232323222232325335332300100122333015010232253355335300233"
, ByteString
"00622222222222200b262101510131014133005005001323001001223330180102253353232533532325335333"
, ByteString
"573466e3cc05c008c05c0040680644ccd5cd19b87301d002301d00101a0191019357420046ae840084ccc048d5"
, ByteString
"d09aba20022222333016357426ae8801488894cd4c8c94cd4cc068d5d08011aba100113253353001357426ae88"
, ByteString
"00c854cd4c008d5d09aba20032132532335333573466e1d200035573a00404e04c264a66a666ae68cdc3a40006"
, ByteString
"aae740040a009c4cc080d5d09aab9e003357426aae780044c00926375400626002931199810002111199811803"
, ByteString
"111299a999ab9a3370e00c00605a0582a66a666ae68cdc38028010168160999ab9a3370e00800205a058205820"
, ByteString
"584054404e6ea8008408c54cd4c004d5d09aba2002210231023301d2001102135573c6ea8014d55cf1baa00815"
, ByteString
"33533330132332300100123302602225335333573466e1d2000375a6aae7800408c08848cc00c00c0044808cdd"
, ByteString
"580091199980a9199ab9a3370e90001bad00102302222333573466e1cdd68011bad00102402337560046eac004"
, ByteString
"01c00c54cd54c8cd4ccd5cd19b8748000d55ce9baa00702102015335333573466e1d200035573a6ea800c08408"
, ByteString
"040844c00526130014988c94c8cd4ccd5cd19b8748008d55ce801011811099299a999ab9a3370e90011aab9d00"
, ByteString
"10240231333573466e3cdd71aba135573c0066eb8d5d09aab9e00102402313002498dd500289800a4c4a66a666"
, ByteString
"ae68cdc3a40086aae7400808c0884c94cd4ccd5cd19b8748010d55ce8008120118999ab9a3375e6ae84d55cf00"
, ByteString
"19aba135573c00204804620466ea80144088dd50038a99a80290a99a80110999ab9a3371e00400204404220402"
, ByteString
"a66a002420402040203e203e203e4646a002002c4646a002002c202e6aae78dd50031aab9e3754004224460040"
, ByteString
"08266008008002002002660024444444444440184c20222c44646464646464646464646466666666666601a6eb"
, ByteString
"0d5d08059bac357420146eb0d5d08049bab357420106eacd5d08039bac3574200c6eacd5d08029aba100437586"
, ByteString
"ae8400cdd59aba100237566ae84004c064d5d09aba2001357440026ae88004d5d10009aba2001357440026ae88"
, ByteString
"004d5d10009aba2001357440026ae88004d55cf1baa357426aae78dd5002111911198018010009918008009111"
, ByteString
"99980b1199980b900a111199180080091980d80b9299a98059aab9e00112330030030011201800500201522233"
, ByteString
"330192332300100123301b01725335300b35573c00224660060060022403000c4446464a66a666ae68cdd78011"
, ByteString
"aab9d00501a019153353300c35573c0106aae780144ccc02c02c01c010406454cd4c034d55cf00409998058058"
, ByteString
"03804899800a99a98069aab9e00514bd6f7b630099aba00054bd6f7b6300021918008009111999810100e11119"
, ByteString
"299a980980089998038038030018a99a999ab9a3375e6aae7401002008007c54cd4cc048d55cf0070008999808"
, ByteString
"80880699a80b803001880f89991980400400099aba000400600335573c00600203c6aae7401801005c008050cc"
, ByteString
"8c00400488488cccc0448008888cd4cc01c01c48004008cd5d000180200100789000911929919a999ab9a3370e"
, ByteString
"90001aab9d00200c00b1325335333573466e1d200035573a00201a0182666ae68cdc79bae357426aae7800cdd7"
, ByteString
"1aba135573c00201a01826004931baa0031300149894cd4ccd5cd19b8748008d55ce801006005899299a999ab9"
, ByteString
"a3370e90011aab9d00100d00c1333573466e3cdd71aba135573c0066eb8d5d09aab9e00100d00c100c37540062"
, ByteString
"0166ea8008888c94cd4ccd5cd19b8748008d55ce800805805099191998029bad357420046eb4d5d08009bad357"
, ByteString
"426ae88004d5d10009aab9e00113002498dd500191119191919998029aba100337566ae84008d5d080099803ba"
, ByteString
"e357426ae88004d5d10009aba200135573c6ea800c88c8c8c94cd4ccd5cd19b8748008008028024401854cd4cc"
, ByteString
"d5cd19b87480000080280244c8488c00800cc014d5d080089805a481035054310035573c0046aae74004dd5000"
, ByteString
"891000918011aba135573c6ea80048c8c8c94cd4ccd5cd19b87480000080180144dd71aba10011300749010350"
, ByteString
"54310035573c0046aae74004dd5000891001091000919319ab9c001002120012375a6ae84d5d11aab9e3754002"
, ByteString
"444a666aae7c004400c4cc008d5d08009aba200101"
]
SLanguage l
SPlutusV3 ->
[ ByteString
"5905f7010100323232323232323232259323233230010012232330012322595930023300722222222222222220"
, ByteString
"0f2690c0023002460011330060060011918008009119802112c99192c99192999ab9a3371e602c004602c00226"
, ByteString
"66ae68cdc3980b801180b800c0020043002357420046ae8400a26660226ae84d5d1001111119980a9aba135744"
, ByteString
"00a4444b26464b2660326ae84008d5d0800c4c964c004d5d09aba200390ac98011aba135744007213253233357"
, ByteString
"3466e1d200035573a004264a666ae68cdc3a40006aae740044cc07cd5d09aab9e003357426aae780044c009263"
, ByteString
"7540062600293119980f8021111998110031112999ab9a3370e00c0062a666ae68cdc38028010999ab9a3370e0"
, ByteString
"080030008010c0086004500228011baa0028c0091593001357426ae8800a430028c000301c20018c0086aae78d"
, ByteString
"d50029aab9e37540111593333014233230010012330208001199ab9a3370e90001bad35573c002466006006002"
, ByteString
"5002375600244666602c4666ae68cdc3a40006eb400600100222333573466e1cdd68011bad0018004008dd5801"
, ByteString
"1bab0010070038aca99199ab9a3370e90001aab9d375400e2a666ae68cdc3a40006aae74dd50018c0004c00526"
, ByteString
"130014988c94c8ccd5cd19b8748008d55ce8010992999ab9a3370e90011aab9d0011333573466e3cdd71aba135"
, ByteString
"573c0066eb8d5d09aab9e00180040084c00926375400a260029312999ab9a3370e90021aab9d00213253335734"
, ByteString
"66e1d200435573a0022666ae68cdd79aba135573c0066ae84d55cf000c0020043002375400a3002375400f1590"
, ByteString
"0590ac801484ccd5cd19b8f002001800400a30024564006430028c0008c0091801230021194800c004c4652003"
, ByteString
"00134600435573c6ea8018d55cf1baa0028c00400913300400400100080118074008cc00488888888888888880"
, ByteString
"409888c8c8c8c8c8c8c8c8c8c8c8c8c8c8c8c8cccccccccccccccc048dd61aba101037586ae8403cdd61aba100"
, ByteString
"e375a6ae84034dd59aba100c37586ae8402cdd59aba100a357420126eb0d5d08041bab3574200e6eacd5d08031"
, ByteString
"bae3574200a6eacd5d08021bac3574200660026ae84008c004d5d09aba2002301875a6ae88004d5d10009aba20"
, ByteString
"01357440026ae88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aa"
, ByteString
"b9e37546ae84d55cf1baa00422322233003002001323001001222333300f233330102800111199180080091980"
, ByteString
"a4000964c02cd55cf000c48cc00c00c006250020028014000888cccc0488cc8c0040048cc0520004b260166aae"
, ByteString
"780062466006006003128010018888c8c94ccd5cd19baf00235573a00a2b2660186aae78020d55cf002c4ccc02"
, ByteString
"c02c01c01230020ac98069aab9e0088999805805803804c4cc00564c034d55cf002c52f5bded8c1133574000a9"
, ByteString
"7adef6c600020c8c004004888cccc064a00444464b2602600313330070070060038a999ab9a3375e6aae740100"
, ByteString
"20564cc048d55cf007000c4ccc044044034cd405401800e300209991980400400099aba00040060031aab9e003"
, ByteString
"0018001aab9d006004800001400229344c01d24103505435001991800800910911999806100111119a99803803"
, ByteString
"8900080119aba0003004002800090009119299199ab9a3370e90001aab9d0021325333573466e1d200035573a0"
, ByteString
"022666ae68cdc79bae357426aae7800cdd71aba135573c0030008010980124c6ea800c4c0052625333573466e1"
, ByteString
"d200235573a004264a666ae68cdc3a40046aae740044ccd5cd19b8f375c6ae84d55cf0019bae357426aae78006"
, ByteString
"00100218011baa00318011baa002222325333573466e1d200235573a0022646466600a6eb4d5d08011bad35742"
, ByteString
"0026eb4d5d09aba2001357440026aae780044c009263754006444646464666600a6ae8400cdd59aba100235742"
, ByteString
"0026600eeb8d5d09aba2001357440026ae88004d55cf1baa003223232325333573466e1d200200218010a999ab"
, ByteString
"9a3370e90000010c004c014d5d080084c0192401035054310035573c0046aae74004dd5000919319ab9c001800"
, ByteString
"11bae357426aae78dd500091bad357426ae88d55cf1baa00122253335573e00220062660046ae84004d5d10009"
]