8
8
{-# LANGUAGE RecordWildCards #-}
9
9
{-# LANGUAGE ScopedTypeVariables #-}
10
10
{-# LANGUAGE TypeApplications #-}
11
+ {-# LANGUAGE TypeOperators #-}
11
12
12
13
-- | Implementation of Hyperlane natives.
13
14
module Crypto.Hash.HyperlaneNatives
@@ -48,7 +49,7 @@ import Data.Text qualified as Text
48
49
import Data.Text.Encoding qualified as Text
49
50
import Data.Text.Read qualified as Text
50
51
import Data.WideWord.Word256 (Word256 (.. ))
51
- import Data.Word (Word8 , Word32 )
52
+ import Data.Word (Word8 , Word16 , Word32 )
52
53
import Ethereum.Misc (keccak256 , _getKeccak256Hash , _getBytesN )
53
54
import Pact.JSON.Decode qualified as J
54
55
import Pact.Types.Exp (Literal (.. ))
@@ -158,9 +159,9 @@ data HyperlaneMessage = HyperlaneMessage
158
159
deriving stock (Eq , Show )
159
160
160
161
data TokenMessageERC20 = TokenMessageERC20
161
- { tmRecipient :: ByteString -- variable
162
- , tmAmount :: Word256 -- uint256
163
- , tmChainId :: Word256 -- uint256
162
+ { tmAmount :: Word256 -- uint256
163
+ , tmChainId :: Word16 -- uint16
164
+ , tmRecipient :: ByteString -- variable
164
165
}
165
166
deriving stock (Eq , Show )
166
167
@@ -170,7 +171,7 @@ data TokenMessageERC20 = TokenMessageERC20
170
171
171
172
packHyperlaneMessage :: HyperlaneMessage -> Builder
172
173
packHyperlaneMessage (HyperlaneMessage {.. }) =
173
- BB. word8 hmVersion
174
+ BB. word8 hmVersion
174
175
<> BB. word32BE hmNonce
175
176
<> BB. word32BE hmOriginDomain
176
177
<> BB. byteString hmSender
@@ -217,31 +218,15 @@ packHyperlaneMessage (HyperlaneMessage{..}) =
217
218
-- 5D7D
218
219
packTokenMessageERC20 :: TokenMessageERC20 -> Builder
219
220
packTokenMessageERC20 t =
220
- word256BE 96
221
- <> word256BE (tmAmount t)
222
- <> word256BE (tmChainId t)
223
- <> word256BE recipientSize
224
- <> BB. byteString recipient
225
- where
226
- (recipient, recipientSize) = padRight (tmRecipient t)
221
+ word256BE (tmAmount t)
222
+ <> BB. word16BE (tmChainId t)
223
+ <> BB. byteString (tmRecipient t)
227
224
228
225
unpackTokenMessageERC20 :: Get TokenMessageERC20
229
226
unpackTokenMessageERC20 = do
230
- firstOffset <- getWord256BE
231
- unless (firstOffset == 96 ) $ do
232
- fail $ " TokenMessage firstOffset expected 96, found " ++ show firstOffset
233
-
234
227
tmAmount <- getWord256BE
235
- tmChainId <- getWord256BE
236
-
237
- recipientSize <- getWord256BE
238
- tmRecipient <- do
239
- let size = fromIntegral @ Word256 @ Int recipientSize
240
- recipient <- BS. take size
241
- <$> Bin. getByteString (fromIntegral @ Word256 @ Int (recipientSize + restSize recipientSize))
242
- if BS. length recipient < size
243
- then fail " TokenMessage recipient was smaller than expected"
244
- else pure recipient
228
+ tmChainId <- Bin. getWord16be
229
+ tmRecipient <- BL. toStrict <$> Bin. getRemainingLazyByteString
245
230
246
231
pure $ TokenMessageERC20 {.. }
247
232
@@ -274,11 +259,13 @@ decodeBase64AndValidate key expected s = do
274
259
275
260
return decoded
276
261
277
- parseChainId :: Text -> Either HyperlaneError Word256
262
+ parseChainId :: forall a . ( a ~ Word16 ) => Text -> Either HyperlaneError a
278
263
parseChainId s = do
279
- cid <- first (HyperlaneErrorInvalidChainId . Text. pack) $ Text. decimal s
280
- unless (fst cid >= 0 ) $ throwError $ HyperlaneErrorInvalidChainId " can't be negative"
281
- return $ fst cid
264
+ (cid, _) <- first (HyperlaneErrorInvalidChainId . Text. pack) $ Text. decimal s
265
+ unless (cid >= minBound && cid <= maxBound ) $ do
266
+ throwError $ HyperlaneErrorInvalidChainId $ Text. pack $
267
+ " ChainId must be in [" <> show @ a minBound <> " , " <> show @ a maxBound <> " ]"
268
+ pure cid
282
269
283
270
------------------------------------------------------
284
271
-- Hyperlane Message Pact Object Decoding --
@@ -370,8 +357,8 @@ getWord256BE = do
370
357
--
371
358
-- > padRight "hello world"
372
359
-- ("hello world\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL",11)
373
- padRight :: ByteString -> (ByteString , Word256 )
374
- padRight s =
360
+ _padRight :: ByteString -> (ByteString , Word256 )
361
+ _padRight s =
375
362
let
376
363
size = BS. length s
377
364
missingZeroes = restSize size
0 commit comments