Skip to content

Commit

Permalink
Add a builtin for decoding TokenMessage for hyperlane SPI (#1344)
Browse files Browse the repository at this point in the history
* Add hyperlane-decode-token-message with gas

* include chainid in TokenMessage encoding

* add principal check for recipient

* TokenMessage recipient parsed as guard

* add new builtin to pact411natives and suppress a debugging error message

* exhaust the TokenMessage when parsing

* use wide-word instead of doubleword

* remove stale TODOs

* cleanup more comments

* Set the empirically measured cas cost for TokenMessage decoding

* fix example in native definition

* fix examples

* rename builtin to hyperlane-decode-token-message

* use base64-unpadded encoding/decoding for tokenmessage

* fix gas costing and add gas tests

* lower bound for binary dependency

* cleanup tokenmessage decoder comments and variable names

* remove padding from encoded message in tokenmessage decoding example

* gasmodelspec remove buildin from list of gas-untested

* update example encoding
  • Loading branch information
imalsogreg authored Feb 22, 2024
1 parent 397ebc9 commit d5279f4
Show file tree
Hide file tree
Showing 9 changed files with 203 additions and 11 deletions.
26 changes: 19 additions & 7 deletions docs/en/pact-functions.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,14 +5,14 @@

Constant denoting the ASCII charset

Constant:
Constant:
  `CHARSET_ASCII:integer = 0`

### CHARSET_LATIN1 {#CHARSET_LATIN1}

Constant denoting the Latin-1 charset ISO-8859-1

Constant:
Constant:
  `CHARSET_LATIN1:integer = 1`

### at {#at}
Expand Down Expand Up @@ -765,7 +765,7 @@ Top level only: this function will fail if used in module code.

Select rows from TABLE using QRY as a predicate with both key and value, and then accumulate results of the query in CONSUMER. Output is sorted by the ordering of keys.
```lisp
(let*
(let*
((qry (lambda (k obj) true)) ;; select all rows
(f (lambda (k obj) [(at 'firstName obj), (at 'b obj)]))
)
Expand Down Expand Up @@ -924,7 +924,7 @@ pact> (add-time (time "2016-07-22T12:00:00Z") 15)
*n* `integer` *→* `decimal`


N days, for use with 'add-time'
N days, for use with 'add-time'
```lisp
pact> (add-time (time "2016-07-22T12:00:00Z") (days 1))
"2016-07-23T12:00:00Z"
Expand Down Expand Up @@ -962,7 +962,7 @@ pact> (format-time "%F" (time "2016-07-22T12:00:00Z"))
*n* `integer` *→* `decimal`


N hours, for use with 'add-time'
N hours, for use with 'add-time'
```lisp
pact> (add-time (time "2016-07-22T12:00:00Z") (hours 1))
"2016-07-22T13:00:00Z"
Expand All @@ -976,7 +976,7 @@ pact> (add-time (time "2016-07-22T12:00:00Z") (hours 1))
*n* `integer` *→* `decimal`


N minutes, for use with 'add-time'.
N minutes, for use with 'add-time'.
```lisp
pact> (add-time (time "2016-07-22T12:00:00Z") (minutes 1))
"2016-07-22T12:01:00Z"
Expand All @@ -1000,7 +1000,7 @@ pact> (parse-time "%F" "2016-09-12")
*utcval* `string` *→* `time`


Construct time from UTCVAL using ISO8601 format (%Y-%m-%dT%H:%M:%SZ).
Construct time from UTCVAL using ISO8601 format (%Y-%m-%dT%H:%M:%SZ).
```lisp
pact> (time "2016-07-22T11:26:35Z")
"2016-07-22T11:26:35Z"
Expand Down Expand Up @@ -1817,6 +1817,18 @@ pact> (poseidon-hash-hack-a-chain 1 2 3 4 5 6 7 8)

## Hyperlane {#Hyperlane}

### hyperlane-decode-token-message {#hyperlane-decode-token-message}

*x* `string` *→* `object:*`


Decode a base-64 encoded Hyperlane Token Message into an object `{recipient:GUARD, amount:DECIMAL, chainId:STRING}`.
```lisp
pact> (hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGF7InByZWQiOiAia2V5cy1hbGwiLCAia2V5cyI6WyJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2Il19AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA==")
{"amount": 0.000000000000000123,"chainId": "4","recipient": KeySet {keys: [da1a339bd82d2c2e9180626a00dc043275deb3ababb27b5738abf6b9dcee8db6],pred: keys-all}}
```


### hyperlane-message-id {#hyperlane-message-id}

*x* `object:*` *→* `string`
Expand Down
1 change: 1 addition & 0 deletions pact.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -207,6 +207,7 @@ library
, base >= 4.18.0.0
, base16-bytestring >=0.1.1.6
, base64-bytestring >=1.0.0.1
, binary >=0.8.9.1
-- base64-bytestring >=1.2.0.0 is less lenient then previous versions, which can cause pact failures (e.g. (env-hash "aa"))
, bound >=2
, bytestring >=0.10.8.1
Expand Down
6 changes: 6 additions & 0 deletions src/Pact/Gas/Table.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ data GasCostConfig = GasCostConfig
, _gasCostConfig_poseidonHashHackAChainQuadraticGasFactor :: Gas
, _gasCostConfig_poseidonHashHackAChainLinearGasFactor :: Gas
, _gasCostConfig_hyperlaneMessageIdGasPerRecipientOneHundredBytes :: MilliGas
, _gasCostConfig_hyperlaneDecodeTokenMessageGasPerOneHundredBytes :: MilliGas
}

defaultGasConfig :: GasCostConfig
Expand Down Expand Up @@ -83,6 +84,7 @@ defaultGasConfig = GasCostConfig
, _gasCostConfig_poseidonHashHackAChainLinearGasFactor = 50
, _gasCostConfig_poseidonHashHackAChainQuadraticGasFactor = 38
, _gasCostConfig_hyperlaneMessageIdGasPerRecipientOneHundredBytes = MilliGas 47
, _gasCostConfig_hyperlaneDecodeTokenMessageGasPerOneHundredBytes = MilliGas 50
}

defaultGasTable :: Map Text Gas
Expand Down Expand Up @@ -239,6 +241,7 @@ defaultGasTable =

,("poseidon-hash-hack-a-chain", 124)
,("hyperlane-message-id", 2)
,("hyperlane-decode-token-message", 2)
]

{-# NOINLINE defaultGasTable #-}
Expand Down Expand Up @@ -339,6 +342,9 @@ tableGasModel gasConfig =
GHyperlaneMessageId len ->
let MilliGas costPerOneHundredBytes = _gasCostConfig_hyperlaneMessageIdGasPerRecipientOneHundredBytes gasConfig
in MilliGas (costPerOneHundredBytes * div (fromIntegral len) 100)
GHyperlaneDecodeTokenMessage len ->
let MilliGas costPerOneHundredBytes = _gasCostConfig_hyperlaneDecodeTokenMessageGasPerOneHundredBytes gasConfig
in MilliGas (costPerOneHundredBytes * div (fromIntegral len) 100)

in GasModel
{ gasModelName = "table"
Expand Down
2 changes: 1 addition & 1 deletion src/Pact/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -276,7 +276,7 @@ pact410Natives :: [Text]
pact410Natives = ["poseidon-hash-hack-a-chain"]

pact411Natives :: [Text]
pact411Natives = ["enforce-verifier", "hyperlane-message-id"]
pact411Natives = ["enforce-verifier", "hyperlane-message-id", "hyperlane-decode-token-message"]

initRefStore :: RefStore
initRefStore = RefStore nativeDefs
Expand Down
129 changes: 129 additions & 0 deletions src/Pact/Native.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE MultiWayIf #-}
-- |
Expand Down Expand Up @@ -55,6 +56,7 @@ module Pact.Native
, describeNamespaceSchema
, dnUserGuard, dnAdminGuard, dnNamespaceName
, cdPrevBlockHash
, encodeTokenMessage
) where

import Control.Arrow hiding (app, first)
Expand All @@ -64,22 +66,30 @@ import Control.Monad
import Control.Monad.IO.Class
import qualified Data.Attoparsec.Text as AP
import Data.Bifunctor (first)
import Data.Binary (get, put)
import Data.Binary.Get (Get, runGetOrFail, getByteString, isEmpty)
import Data.Binary.Put (Put, runPut, putByteString)
import Data.Bool (bool)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Base64.URL as B64URL
import qualified Data.Char as Char
import Data.Bits
import Data.Decimal (Decimal)
import Data.Default
import Data.Functor(($>))
import Data.Foldable
import Data.List (isPrefixOf)
import qualified Data.HashMap.Strict as HM
import qualified Data.Map.Strict as M
import qualified Data.List as L (nubBy)
import Data.Ratio ((%))
import qualified Data.Set as S
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
import qualified Data.Text as Text
import qualified Data.Text.Encoding as T
import Data.WideWord.Word256
import Pact.Time
import qualified Data.Vector as V
import qualified Data.Vector.Algorithms.Intro as V
Expand Down Expand Up @@ -111,6 +121,7 @@ import Crypto.Hash.PoseidonNative (poseidon)
import Crypto.Hash.HyperlaneMessageId (hyperlaneMessageId)

import qualified Pact.JSON.Encode as J
import qualified Pact.JSON.Decode as J

-- | All production native modules.
natives :: [NativeModule]
Expand Down Expand Up @@ -1579,6 +1590,7 @@ poseidonHackAChainDef = defGasRNative
hyperlaneDefs :: NativeModule
hyperlaneDefs = ("Hyperlane",)
[ hyperlaneMessageIdDef
, hyperlaneDecodeTokenMessageDef
]

hyperlaneMessageIdDef :: NativeDef
Expand Down Expand Up @@ -1609,3 +1621,120 @@ hyperlaneMessageIdDef = defGasRNative
case mRecipient of
Nothing -> error "couldn't decode token recipient"
Just t -> T.encodeUtf8 t

hyperlaneDecodeTokenMessageDef :: NativeDef
hyperlaneDecodeTokenMessageDef =
defGasRNative
"hyperlane-decode-token-message"
hyperlaneDecodeTokenMessageDef'
(funType tTyObjectAny [("x", tTyString)])
["(hyperlane-decode-token-message \"AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGF7InByZWQiOiAia2V5cy1hbGwiLCAia2V5cyI6WyJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2Il19AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA\")"]
"Decode a base-64-unpadded encoded Hyperlane Token Message into an object `{recipient:GUARD, amount:DECIMAL, chainId:STRING}`."
where
hyperlaneDecodeTokenMessageDef' :: RNativeFun e
hyperlaneDecodeTokenMessageDef' i args = case args of

[TLitString msg] ->
-- We do not need to handle historical b64 error message shimming
-- or decoding from non-canonical strings in this base-64 decoder,
-- because this native is added in a Pact version that later than when
-- we moved to base64-bytestring >= 1.0, which behaves succeeds and
-- fails in exactly the cases we expect.
-- (The only change we make to its output is to strip error messages).
computeGas' i (GHyperlaneDecodeTokenMessage (T.length msg)) $
case B64URL.decodeUnpadded (T.encodeUtf8 msg) of
Left _ -> evalError' i "Failed to base64-decode token message"
Right bytes -> do
case runGetOrFail (getTokenMessageERC20 <* eof) (BS.fromStrict bytes) of
-- In case of Binary decoding failure, emit a terse error message.
-- If the error message begins with TokenError, we know that we
-- created it, and it is going to be stable (non-forking).
-- If it does not start with TokenMessage, it may have come from
-- the Binary library, and we will suppress it to shield ourselves
-- from forking behavior if we update our Binary version.
Left (_,_,e) | "TokenMessage" `isPrefixOf` e -> evalError' i $ "Decoding error: " <> pretty e
Left _ -> evalError' i "Decoding error: binary decoding failed"
Right (_,_,(amount, chain, recipient)) ->
case PGuard <$> J.eitherDecode (BS.fromStrict $ T.encodeUtf8 recipient) of
Left _ -> evalError' i $ "Could not parse recipient into a guard"
Right g ->
pure $ toTObject TyAny def
[("recipient", fromPactValue g)
,("amount", TLiteral (LDecimal $ wordToDecimal amount) def)
,("chainId", toTerm chain)
]
_ -> argsError i args

-- The TokenMessage contains a recipient (text) and an amount (word-256).
-- A schematic of the message format:
-- 0000000000000000000000000000000000000000000000000000000000000060 # offset of the recipient string = 96, because first three lines are 32 bytes each
-- 0000000000000000000000000000000000000000000000008ac7230489e80000 # amount = 10000000000000000000
-- 0000000000000000000000000000000000000000000000000000000000000000 # chainId = 0
-- 0000000000000000000000000000000000000000000000000000000000000062 # recipientSize = 98
-- 7B2270726564223A20226B6579732D616C6C222C20226B657973223A205B2264 # {"pred": "keys-all", "keys": ["da1a339bd82d2c2e9180626a00dc043275deb3ababb27b5738abf6b9dcee8db6"]}
-- 6131613333396264383264326332653931383036323661303064633034333237
-- 3564656233616261626232376235373338616266366239646365653864623622
-- 5D7D
getTokenMessageERC20 :: Get (Word256, ChainId, Text)
getTokenMessageERC20 = do

-- Parse the size of the following amount field.
firstOffset <- fromIntegral @Word256 @Int <$> getWord256be
unless (firstOffset == 96)
(fail $ "TokenMessage firstOffset expected 96, found " ++ show firstOffset)
tmAmount <- getWord256be
tmChainId <- getWord256be

recipientSize <- getWord256be
tmRecipient <- T.decodeUtf8 <$> getRecipient recipientSize

return (tmAmount, ChainId { _chainId = T.pack (show (toInteger tmChainId))}, tmRecipient)
where
getWord256be = get @Word256

-- | Reads a given number of bytes and the rest because binary data padded up to 32 bytes.
getRecipient :: Word256 -> Get BS.ByteString
getRecipient size = do
recipient <- BS.take (fromIntegral size) <$> getByteString (fromIntegral $ size + restSize size)
if BS.length recipient < fromIntegral size
then fail "TokenMessage recipient was smaller than expected"
else pure recipient


wordToDecimal :: Word256 -> Decimal
wordToDecimal w =
let ethInWei = 1000000000000000000 -- 1e18
in fromRational (toInteger w % ethInWei)

eof :: Get ()
eof = do
done <- isEmpty
unless done $ fail "pending bytes in input"

-- | Helper function for creating TokenMessages encoded in the ERC20 format
-- and base64url encoded. Used for generating test data.
encodeTokenMessage :: BS.ByteString -> Word256 -> Word256 -> Text
encodeTokenMessage recipient amount chain = T.decodeUtf8 $ B64URL.encodeUnpadded (BS.toStrict bytes)
where
bytes = runPut $ do
putWord256be (96 :: Word256)
putWord256be amount
putWord256be chain
putWord256be recipientSize
putByteString recipientBytes

(recipientBytes, recipientSize) = padRight recipient

putWord256be :: Word256 -> Put
putWord256be = put @Word256

padRight :: BS.ByteString -> (BS.ByteString, Word256)
padRight s =
let
size = BS.length s
missingZeroes = restSize size
in (s <> BS.replicate missingZeroes 0, fromIntegral size)

-- | Returns the modular of 32 bytes.
restSize :: Integral a => a -> a
restSize size = (32 - size) `mod` 32
4 changes: 4 additions & 0 deletions src/Pact/Types/Gas.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,6 +186,9 @@ data GasArgs
-- ^ Cost of the hyperlane-message-id on this size (in bytes) of the
-- hyperlane TokenMessage Recipient, which is the only variable-length
-- part of a HyperlaneMessage
| GHyperlaneDecodeTokenMessage !Int
-- ^ Cost of hyperlane-decode-token-message on this size (in bytes) of the
-- hyperlane TokenMessage base64-encoded string.

data IntOpThreshold
= Pact43IntThreshold
Expand Down Expand Up @@ -255,6 +258,7 @@ instance Pretty GasArgs where
GFormatValues s args -> "GFormatValues:" <> pretty s <> pretty (V.toList args)
GPoseidonHashHackAChain len -> "GPoseidonHashHackAChain:" <> pretty len
GHyperlaneMessageId len -> "GHyperlaneMessageId:" <> pretty len
GHyperlaneDecodeTokenMessage len -> "GHyperlaneDecodeTokenMessage:" <> pretty len

newtype GasLimit = GasLimit ParsedInteger
deriving (Eq,Ord,Generic)
Expand Down
1 change: 1 addition & 0 deletions tests/GasModelSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ untestedNativesCheck = do
, "dec"
, "list"
, "continue"
, "hyperlane-decode-token-message"
])

allGasTestsAndGoldenShouldPass :: Spec
Expand Down
3 changes: 0 additions & 3 deletions tests/pact/hyperlane-message-id.repl

This file was deleted.

42 changes: 42 additions & 0 deletions tests/pact/hyperlane.repl
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
;; Test hyperlane builtins.

(env-data
{ "test-keys" : {"pred": "keys-all", "keys": ["da1a339bd82d2c2e9180626a00dc043275deb3ababb27b5738abf6b9dcee8db6"]}
})

(expect "computes the correct message id" "0x97d98aa7fdb548f43c9be37aaea33fca79680247eb8396148f1df10e6e0adfb7" (hyperlane-message-id {"destinationDomain": 1,"nonce": 325,"originDomain": 626,"recipient": "0x71C7656EC7ab88b098defB751B7401B5f6d8976F","sender": "0x6b622d746f6b656e2d726f75746572","tokenMessage": {"amount": 10000000000000000000.0,"recipient": "0x71C7656EC7ab88b098defB751B7401B5f6d8976F"},"version": 1}))

; Decoding a valid TokenMessage should succeed.
(expect "decodes the correct TokenMessage"
{ "amount":0.000000000000000123,
"chainId": "4",
"recipient": (read-keyset 'test-keys)
}
(hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGF7InByZWQiOiAia2V5cy1hbGwiLCAia2V5cyI6WyJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2Il19AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA")
)

; Decoding a valid TokenMessage should succeed.
(expect-failure "decoding fails for base64-padded messages"
(hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGF7InByZWQiOiAia2V5cy1hbGwiLCAia2V5cyI6WyJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2Il19AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA==")
)

; This TokenMessage was encoded with the recipient
; "k:462e97a099987f55f6a2b52e7bfd52a36b4b5b470fed0816a3d9b26f9450ba69".
; It should fail to decode because "k:462e97a099987f55f6a2b52e7bfd52a36b4b5b470fed0816a3d9b26f9450ba69"
; is a principal, not a guard. (Recipient must be a guard encoded in json).
(expect-failure
"Decoding requires recipient to be a guard."
(hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEJrOjQ2MmU5N2EwOTk5ODdmNTVmNmEyYjUyZTdiZmQ1MmEzNmI0YjViNDcwZmVkMDgxNmEzZDliMjZmOTQ1MGJhNjkAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA=")
)

; Gas tests.
(env-gasmodel "table")
(env-gaslimit 10000)

(env-gas)
(hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGF7InByZWQiOiAia2V5cy1hbGwiLCAia2V5cyI6WyJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2Il19AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA")
(expect "Normal message decoding should cost 2 gas" 2 (env-gas))

(env-gas 0)
(hyperlane-decode-token-message "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAewAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABfwgIHsgInByZWQiOiAia2V5cy1hbnkiLCAia2V5cyI6IFsgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiLCAiZGExYTMzOWJkODJkMmMyZTkxODA2MjZhMDBkYzA0MzI3NWRlYjNhYmFiYjI3YjU3MzhhYmY2YjlkY2VlOGRiNiIsICJkYTFhMzM5YmQ4MmQyYzJlOTE4MDYyNmEwMGRjMDQzMjc1ZGViM2FiYWJiMjdiNTczOGFiZjZiOWRjZWU4ZGI2IiwgImRhMWEzMzliZDgyZDJjMmU5MTgwNjI2YTAwZGMwNDMyNzVkZWIzYWJhYmIyN2I1NzM4YWJmNmI5ZGNlZThkYjYiIF0gfQAAAAA")
(expect "Decoding a message with about 2000 characters should cost 3 gas" 3 (env-gas))

0 comments on commit d5279f4

Please sign in to comment.