From c2c47bf5cc656c041439615aa65d23dd3443083a Mon Sep 17 00:00:00 2001 From: martyall Date: Wed, 13 Sep 2023 22:36:35 -0700 Subject: [PATCH] use reifyType to cover literally every possible case --- src/Network/Ethereum/Web3.purs | 6 +- src/Network/Ethereum/Web3/Solidity.purs | 9 +- .../Ethereum/Web3/Solidity/AbiEncoding.purs | 28 +- src/Network/Ethereum/Web3/Solidity/Bytes.purs | 25 +- .../Ethereum/Web3/Solidity/EncodingType.purs | 21 +- src/Network/Ethereum/Web3/Solidity/Int.purs | 32 +- src/Network/Ethereum/Web3/Solidity/Size.purs | 179 +++--- src/Network/Ethereum/Web3/Solidity/UInt.purs | 29 +- .../Ethereum/Web3/Solidity/Vector.purs | 25 +- .../Web3Spec/Encoding/ContainersSpec.purs | 596 ++++++------------ test/web3/Web3Spec/Live/Utils.purs | 9 +- 11 files changed, 384 insertions(+), 575 deletions(-) diff --git a/src/Network/Ethereum/Web3.purs b/src/Network/Ethereum/Web3.purs index 4944864..75e6868 100644 --- a/src/Network/Ethereum/Web3.purs +++ b/src/Network/Ethereum/Web3.purs @@ -9,11 +9,7 @@ module Network.Ethereum.Web3 import Network.Ethereum.Web3.Contract (class EventFilter, event, eventFilter, call, sendTx, deployContract, mkDataField) import Network.Ethereum.Web3.Contract.Events (event', EventHandler, MultiFilterStreamState(..), FilterStreamState, ChangeReceipt) import Network.Ethereum.Web3.Solidity - ( class KnownSize - , sizeVal - , class IntSize - , class ByteSize - , Address + ( Address , BigNumber , ByteString , BytesN diff --git a/src/Network/Ethereum/Web3/Solidity.purs b/src/Network/Ethereum/Web3/Solidity.purs index bcf058b..c4dc1fd 100644 --- a/src/Network/Ethereum/Web3/Solidity.purs +++ b/src/Network/Ethereum/Web3/Solidity.purs @@ -1,6 +1,5 @@ module Network.Ethereum.Web3.Solidity - ( module Network.Ethereum.Web3.Solidity.Size - , module Network.Ethereum.Web3.Solidity.Vector + ( module Network.Ethereum.Web3.Solidity.Vector , module Network.Ethereum.Web3.Solidity.Bytes , module Network.Ethereum.Web3.Solidity.Tuple , module Network.Ethereum.Web3.Solidity.Generic @@ -12,12 +11,6 @@ module Network.Ethereum.Web3.Solidity , module Data.ByteString ) where -import Network.Ethereum.Web3.Solidity.Size - ( class KnownSize - , sizeVal - , class IntSize - , class ByteSize - ) import Network.Ethereum.Web3.Solidity.Vector (Vector, unVector, nilVector, vCons, (:<), vectorLength, toVector) import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, proxyBytesN, update, fromByteString) import Network.Ethereum.Web3.Solidity.Tuple diff --git a/src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs b/src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs index abf8ed2..e6e1c62 100644 --- a/src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs +++ b/src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs @@ -22,6 +22,7 @@ import Data.ByteString (toUTF8, fromUTF8, length) as BS import Data.Either (Either) import Data.Functor.Tagged (Tagged, tagged, untagged) import Data.Maybe (fromJust, maybe) +import Data.Reflectable (class Reflectable, reflectType) import Data.String (splitAt) import Data.Traversable (for, scanl) import Data.Tuple (Tuple(..)) @@ -32,7 +33,6 @@ import Network.Ethereum.Types (Address, BigNumber, embed, mkAddress, unAddress) import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, update, proxyBytesN) import Network.Ethereum.Web3.Solidity.EncodingType (class EncodingType, isDynamic) import Network.Ethereum.Web3.Solidity.Int (IntN, unIntN, intNFromBigNumber) -import Network.Ethereum.Web3.Solidity.Size (class ByteSize, class IntSize, class KnownSize, sizeVal) import Network.Ethereum.Web3.Solidity.UInt (UIntN, unUIntN, uIntNFromBigNumber) import Network.Ethereum.Web3.Solidity.Vector (Vector, unVector) import Parsing (ParseError, Parser, ParseState(..), Position(..), ParserT, fail, getParserT, stateParserT, runParser) @@ -92,26 +92,26 @@ instance abiEncodeString :: ABIEncode String where instance abiDecodeString :: ABIDecode String where fromDataParser = BS.fromUTF8 <$> fromDataParser -instance abiEncodeBytesN :: ByteSize n => ABIEncode (BytesN n) where +instance abiEncodeBytesN :: Reflectable n Int => ABIEncode (BytesN n) where toDataBuilder bs = bytesBuilder <<< unBytesN $ bs -instance abiDecodeBytesN :: ByteSize n => ABIDecode (BytesN n) where +instance abiDecodeBytesN :: Reflectable n Int => ABIDecode (BytesN n) where fromDataParser = do let - len = sizeVal (Proxy :: Proxy n) + len = reflectType (Proxy :: Proxy n) zeroBytes = 32 - len raw <- parseBytes len _ <- parseBytes zeroBytes pure <<< update proxyBytesN <<< toByteString $ raw -instance abiEncodeVec :: (EncodingType a, ABIEncode a, KnownSize n) => ABIEncode (Vector n a) where +instance abiEncodeVec :: (EncodingType a, ABIEncode a, Reflectable n Int) => ABIEncode (Vector n a) where toDataBuilder l = if isDynamic (Proxy :: Proxy a) then do let encs = map toDataBuilder (unVector l) lengths = map numberOfBytes encs - len = sizeVal (Proxy :: Proxy n) + len = reflectType (Proxy :: Proxy n) offsets = let seed = 32 * len @@ -121,10 +121,10 @@ instance abiEncodeVec :: (EncodingType a, ABIEncode a, KnownSize n) => ABIEncode else foldMap toDataBuilder $ (unVector l :: Array a) -instance abiDecodeVec :: (EncodingType a, KnownSize n, ABIDecode a) => ABIDecode (Vector n a) where +instance abiDecodeVec :: (EncodingType a, Reflectable n Int, ABIDecode a) => ABIDecode (Vector n a) where fromDataParser = do let - len = sizeVal (Proxy :: Proxy n) + len = reflectType (Proxy :: Proxy n) if isDynamic (Proxy :: Proxy a) then do offsets <- replicateA len uInt256HexParser let @@ -173,31 +173,31 @@ instance abiDecodeArray :: (EncodingType a, ABIDecode a) => ABIDecode (Array a) else replicateA len fromDataParser -instance abiEncodeUint :: IntSize n => ABIEncode (UIntN n) where +instance abiEncodeUint :: Reflectable n Int => ABIEncode (UIntN n) where toDataBuilder a = uInt256HexBuilder <<< unUIntN $ a -instance abiDecodeUint :: IntSize n => ABIDecode (UIntN n) where +instance abiDecodeUint :: Reflectable n Int => ABIDecode (UIntN n) where fromDataParser = do a <- uInt256HexParser maybe (fail $ msg a) pure <<< uIntNFromBigNumber (Proxy :: Proxy n) $ a where msg n = let - size = sizeVal (Proxy :: Proxy n) + size = reflectType (Proxy :: Proxy n) in "Couldn't parse as uint" <> show size <> " : " <> show n -instance abiEncodeIntN :: IntSize n => ABIEncode (IntN n) where +instance abiEncodeIntN :: Reflectable n Int => ABIEncode (IntN n) where toDataBuilder a = int256HexBuilder <<< unIntN $ a -instance abiDecodeIntN :: IntSize n => ABIDecode (IntN n) where +instance abiDecodeIntN :: Reflectable n Int => ABIDecode (IntN n) where fromDataParser = do a <- int256HexParser maybe (fail $ msg a) pure <<< intNFromBigNumber (Proxy :: Proxy n) $ a where msg n = let - size = sizeVal (Proxy :: Proxy n) + size = reflectType (Proxy :: Proxy n) in "Couldn't parse as int" <> show size <> " : " <> show n diff --git a/src/Network/Ethereum/Web3/Solidity/Bytes.purs b/src/Network/Ethereum/Web3/Solidity/Bytes.purs index 6cdad4f..bb558a1 100644 --- a/src/Network/Ethereum/Web3/Solidity/Bytes.purs +++ b/src/Network/Ethereum/Web3/Solidity/Bytes.purs @@ -4,18 +4,19 @@ module Network.Ethereum.Web3.Solidity.Bytes , proxyBytesN , update , fromByteString + , generator ) where import Prelude +import Control.Monad.Gen (class MonadGen) import Data.ByteString (empty, ByteString, Encoding(Hex)) import Data.ByteString as BS import Data.Maybe (Maybe(..), fromJust) +import Data.Reflectable (class Reflectable, reflectType) import Network.Ethereum.Core.HexString (genBytes, toByteString) import Network.Ethereum.Types (mkHexString) -import Network.Ethereum.Web3.Solidity.Size (class KnownSize, sizeVal) import Partial.Unsafe (unsafePartial) -import Test.QuickCheck (class Arbitrary) import Type.Proxy (Proxy(..)) -------------------------------------------------------------------------------- @@ -26,29 +27,29 @@ import Type.Proxy (Proxy(..)) newtype BytesN (n :: Int) = BytesN ByteString derive newtype instance eqBytesN :: Eq (BytesN n) -instance showBytesN :: KnownSize n => Show (BytesN n) where +instance showBytesN :: Show (BytesN n) where show (BytesN bs) = show <<< unsafePartial fromJust <<< mkHexString $ BS.toString bs Hex -instance KnownSize n => Arbitrary (BytesN n) where - arbitrary = do - bs <- genBytes (sizeVal (Proxy :: Proxy n)) - pure $ BytesN $ toByteString bs +generator :: forall n m. Reflectable n Int => MonadGen m => Proxy n -> m (BytesN n) +generator p = do + bs <- genBytes (reflectType p) + pure $ BytesN $ toByteString bs -- | Access the underlying raw bytestring -unBytesN :: forall n. KnownSize n => BytesN n -> ByteString +unBytesN :: forall n. BytesN n -> ByteString unBytesN (BytesN bs) = bs -proxyBytesN :: forall n. KnownSize n => BytesN n +proxyBytesN :: forall n. BytesN n proxyBytesN = BytesN empty -update :: forall n. KnownSize n => BytesN n -> ByteString -> BytesN n +update :: forall n. BytesN n -> ByteString -> BytesN n update _ = BytesN -- | Attempt to coerce a bytestring into one of the appropriate size. -- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes. -fromByteString :: forall proxy n. KnownSize n => proxy n -> ByteString -> Maybe (BytesN n) +fromByteString :: forall proxy n. Reflectable n Int => proxy n -> ByteString -> Maybe (BytesN n) fromByteString _ bs = - if not $ BS.length bs <= sizeVal (Proxy :: Proxy n) then + if not $ BS.length bs <= reflectType (Proxy :: Proxy n) then Nothing else Just $ BytesN bs diff --git a/src/Network/Ethereum/Web3/Solidity/EncodingType.purs b/src/Network/Ethereum/Web3/Solidity/EncodingType.purs index 37adb08..331f0da 100644 --- a/src/Network/Ethereum/Web3/Solidity/EncodingType.purs +++ b/src/Network/Ethereum/Web3/Solidity/EncodingType.purs @@ -5,14 +5,15 @@ module Network.Ethereum.Web3.Solidity.EncodingType ) where import Prelude + import Data.ByteString (ByteString) import Data.Functor.Tagged (Tagged) +import Data.Reflectable (class Reflectable, reflectType) +import Network.Ethereum.Types (Address, BigNumber) import Network.Ethereum.Web3.Solidity.Bytes (BytesN) import Network.Ethereum.Web3.Solidity.Int (IntN) -import Network.Ethereum.Web3.Solidity.Size (class IntSize, class KnownSize, sizeVal) import Network.Ethereum.Web3.Solidity.UInt (UIntN) import Network.Ethereum.Web3.Solidity.Vector (Vector) -import Network.Ethereum.Types (Address, BigNumber) import Type.Proxy (Proxy(..)) class EncodingType :: forall k. k -> Constraint @@ -32,12 +33,12 @@ instance encodingTypeBigNumber :: EncodingType BigNumber where typeName = const "int" isDynamic = const false -instance encodingTypeUIntN :: IntSize n => EncodingType (UIntN n) where - typeName = const $ "uint" <> (show $ sizeVal (Proxy :: Proxy n)) +instance encodingTypeUIntN :: Reflectable n Int => EncodingType (UIntN n) where + typeName = const $ "uint" <> (show $ reflectType (Proxy :: Proxy n)) isDynamic = const false -instance encodingTypeIntN :: IntSize n => EncodingType (IntN n) where - typeName = const $ "int" <> (show $ sizeVal (Proxy :: Proxy n)) +instance encodingTypeIntN :: Reflectable n Int => EncodingType (IntN n) where + typeName = const $ "int" <> (show $ reflectType (Proxy :: Proxy n)) isDynamic = const false instance encodingTypeString :: EncodingType String where @@ -52,18 +53,18 @@ instance encodingTypeArray :: EncodingType a => EncodingType (Array a) where typeName = const "[]" isDynamic = const true -instance encodingTypeBytes :: KnownSize n => EncodingType (BytesN n) where +instance encodingTypeBytes :: Reflectable n Int => EncodingType (BytesN n) where typeName = let - n = show (sizeVal (Proxy :: Proxy n)) + n = show (reflectType (Proxy :: Proxy n)) in const $ "bytes[" <> n <> "]" isDynamic = const false -instance encodingTypeVector :: (KnownSize n, EncodingType a) => EncodingType (Vector n a) where +instance encodingTypeVector :: (Reflectable n Int, EncodingType a) => EncodingType (Vector n a) where typeName = let - n = show (sizeVal (Proxy :: Proxy n)) + n = show (reflectType (Proxy :: Proxy n)) baseTypeName = typeName (Proxy :: Proxy a) in diff --git a/src/Network/Ethereum/Web3/Solidity/Int.purs b/src/Network/Ethereum/Web3/Solidity/Int.purs index 906afc0..9b908b0 100644 --- a/src/Network/Ethereum/Web3/Solidity/Int.purs +++ b/src/Network/Ethereum/Web3/Solidity/Int.purs @@ -2,19 +2,17 @@ module Network.Ethereum.Web3.Solidity.Int ( IntN , unIntN , intNFromBigNumber + , generator ) where import Prelude -import Control.Alternative ((<|>)) -import Control.Monad.Gen as Gen +import Control.Monad.Gen (class MonadGen) import Data.Maybe (Maybe(..), fromJust) -import Data.NonEmpty (NonEmpty(..)) +import Data.Reflectable (class Reflectable, reflectType) import Network.Ethereum.Core.BigNumber (BigNumber, embed, fromString, fromTwosComplement, pow) import Network.Ethereum.Core.HexString (genBytes, unHex) -import Network.Ethereum.Web3.Solidity.Size (class KnownSize, sizeVal) import Partial.Unsafe (unsafePartial) -import Test.QuickCheck (class Arbitrary) import Type.Proxy (Proxy(..)) -------------------------------------------------------------------------------- @@ -28,14 +26,14 @@ derive newtype instance showIntN :: Show (IntN n) derive newtype instance eqIntN :: Eq (IntN n) derive newtype instance ordIntN :: Ord (IntN n) -instance KnownSize n => Arbitrary (IntN n) where - arbitrary = do - bs <- genBytes (sizeVal (Proxy @n) `div` 8) - let - a = - if bs == mempty then zero - else unsafePartial $ fromJust $ fromString $ unHex $ bs - pure $ IntN $ fromTwosComplement (sizeVal (Proxy @n)) a +generator :: forall n m. Reflectable n Int => MonadGen m => Proxy n -> m (IntN n) +generator p = do + bs <- genBytes (reflectType p `div` 8) + let + a = + if bs == mempty then zero + else unsafePartial $ fromJust $ fromString $ unHex $ bs + pure $ IntN $ fromTwosComplement (reflectType (Proxy @n)) a -- | Access the raw underlying integer unIntN :: forall n. IntN n -> BigNumber @@ -43,15 +41,15 @@ unIntN (IntN a) = a -- | Attempt to coerce an signed `BigNumber` into a statically sized one. -- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes. -intNFromBigNumber :: forall n proxy. KnownSize n => proxy n -> BigNumber -> Maybe (IntN n) -intNFromBigNumber proxy a +intNFromBigNumber :: forall n proxy. Reflectable n Int => proxy n -> BigNumber -> Maybe (IntN n) +intNFromBigNumber _ a | a < zero = let - minVal = negate $ (embed 2) `pow` (sizeVal proxy - one) + minVal = negate $ (embed 2) `pow` (reflectType (Proxy @n) - one) in if a < minVal then Nothing else Just <<< IntN $ a | otherwise = let - maxVal = (embed 2) `pow` (sizeVal proxy - one) - one + maxVal = (embed 2) `pow` (reflectType (Proxy @n) - one) - one in if a > maxVal then Nothing else Just <<< IntN $ a diff --git a/src/Network/Ethereum/Web3/Solidity/Size.purs b/src/Network/Ethereum/Web3/Solidity/Size.purs index c414e8d..a533500 100644 --- a/src/Network/Ethereum/Web3/Solidity/Size.purs +++ b/src/Network/Ethereum/Web3/Solidity/Size.purs @@ -1,89 +1,90 @@ -module Network.Ethereum.Web3.Solidity.Size - ( class KnownSize - , sizeVal - , class IntSize - , class ByteSize - ) where - -import Data.Reflectable (class Reflectable, reflectType) -import Type.Proxy (Proxy(..)) - -class Reflectable n Int <= KnownSize (n :: Int) where - sizeVal :: forall proxy. proxy n -> Int - -instance (Reflectable n Int) => KnownSize n where - sizeVal _ = reflectType (Proxy :: Proxy n) - --- | `IntSize` is empty class, if there is instance of `IntSize` for some number it means there --- | is solidity type `int` of that size specific number in like `int16`, `int24` ... `int256` -class KnownSize n <= IntSize (n :: Int) - -instance intSize8 :: IntSize 8 -instance intSize16 :: IntSize 16 -instance intSize24 :: IntSize 24 -instance intSize32 :: IntSize 32 -instance intSize40 :: IntSize 40 -instance intSize48 :: IntSize 48 -instance intSize56 :: IntSize 56 -instance intSize64 :: IntSize 64 -instance intSize72 :: IntSize 72 -instance intSize80 :: IntSize 80 -instance intSize88 :: IntSize 88 -instance intSize96 :: IntSize 96 -instance intSize104 :: IntSize 104 -instance intSize112 :: IntSize 112 -instance intSize120 :: IntSize 120 -instance intSize128 :: IntSize 128 -instance intSize136 :: IntSize 136 -instance intSize144 :: IntSize 144 -instance intSize152 :: IntSize 152 -instance intSize160 :: IntSize 160 -instance intSize168 :: IntSize 168 -instance intSize176 :: IntSize 176 -instance intSize184 :: IntSize 184 -instance intSize192 :: IntSize 192 -instance intSize200 :: IntSize 200 -instance intSize208 :: IntSize 208 -instance intSize216 :: IntSize 216 -instance intSize224 :: IntSize 224 -instance intSize232 :: IntSize 232 -instance intSize240 :: IntSize 240 -instance intSize248 :: IntSize 248 -instance intSize256 :: IntSize 256 - --- | `ByteSize` is empty class, if there is instance of `ByteSize` for some number it means there --- | is solidity type `bytes` of that size specific number in like `bytes1`, `bytes2` ... `bytes32` -class KnownSize n <= ByteSize (n :: Int) - -instance byteSize1 :: ByteSize 1 -instance byteSize2 :: ByteSize 2 -instance byteSize3 :: ByteSize 3 -instance byteSize4 :: ByteSize 4 -instance byteSize5 :: ByteSize 5 -instance byteSize6 :: ByteSize 6 -instance byteSize7 :: ByteSize 7 -instance byteSize8 :: ByteSize 8 -instance byteSize9 :: ByteSize 9 -instance byteSize10 :: ByteSize 10 -instance byteSize11 :: ByteSize 11 -instance byteSize12 :: ByteSize 12 -instance byteSize13 :: ByteSize 13 -instance byteSize14 :: ByteSize 14 -instance byteSize15 :: ByteSize 15 -instance byteSize16 :: ByteSize 16 -instance byteSize17 :: ByteSize 17 -instance byteSize18 :: ByteSize 18 -instance byteSize19 :: ByteSize 19 -instance byteSize20 :: ByteSize 20 -instance byteSize21 :: ByteSize 21 -instance byteSize22 :: ByteSize 22 -instance byteSize23 :: ByteSize 23 -instance byteSize24 :: ByteSize 24 -instance byteSize25 :: ByteSize 25 -instance byteSize26 :: ByteSize 26 -instance byteSize27 :: ByteSize 27 -instance byteSize28 :: ByteSize 28 -instance byteSize29 :: ByteSize 29 -instance byteSize30 :: ByteSize 30 -instance byteSize31 :: ByteSize 31 -instance byteSize32 :: ByteSize 32 +module Network.Ethereum.Web3.Solidity.Size where +-- ( class KnownSize +-- , reflectType +-- , class IntSize +-- , class ByteSize +-- ) where +-- +--import Data.Reflectable (class Reflectable, reflectType) +--import Type.Proxy (Proxy(..)) +-- +--class Reflectable n Int <= KnownSize (n :: Int) where +-- reflectType :: forall proxy. proxy n -> Int +-- +--instance (Reflectable n Int) => KnownSize n where +-- reflectType _ = reflectType (Proxy :: Proxy n) +-- +---- | `IntSize` is empty class, if there is instance of `IntSize` for some number it means there +---- | is solidity type `int` of that size specific number in like `int16`, `int24` ... `int256` +--class KnownSize n <= IntSize (n :: Int) +-- +--instance intSize8 :: IntSize 8 +--instance intSize16 :: IntSize 16 +--instance intSize24 :: IntSize 24 +--instance intSize32 :: IntSize 32 +--instance intSize40 :: IntSize 40 +--instance intSize48 :: IntSize 48 +--instance intSize56 :: IntSize 56 +--instance intSize64 :: IntSize 64 +--instance intSize72 :: IntSize 72 +--instance intSize80 :: IntSize 80 +--instance intSize88 :: IntSize 88 +--instance intSize96 :: IntSize 96 +--instance intSize104 :: IntSize 104 +--instance intSize112 :: IntSize 112 +--instance intSize120 :: IntSize 120 +--instance intSize128 :: IntSize 128 +--instance intSize136 :: IntSize 136 +--instance intSize144 :: IntSize 144 +--instance intSize152 :: IntSize 152 +--instance intSize160 :: IntSize 160 +--instance intSize168 :: IntSize 168 +--instance intSize176 :: IntSize 176 +--instance intSize184 :: IntSize 184 +--instance intSize192 :: IntSize 192 +--instance intSize200 :: IntSize 200 +--instance intSize208 :: IntSize 208 +--instance intSize216 :: IntSize 216 +--instance intSize224 :: IntSize 224 +--instance intSize232 :: IntSize 232 +--instance intSize240 :: IntSize 240 +--instance intSize248 :: IntSize 248 +--instance intSize256 :: IntSize 256 +-- +---- | `ByteSize` is empty class, if there is instance of `ByteSize` for some number it means there +---- | is solidity type `bytes` of that size specific number in like `bytes1`, `bytes2` ... `bytes32` +--class KnownSize n <= ByteSize (n :: Int) +-- +--instance byteSize1 :: ByteSize 1 +--instance byteSize2 :: ByteSize 2 +--instance byteSize3 :: ByteSize 3 +--instance byteSize4 :: ByteSize 4 +--instance byteSize5 :: ByteSize 5 +--instance byteSize6 :: ByteSize 6 +--instance byteSize7 :: ByteSize 7 +--instance byteSize8 :: ByteSize 8 +--instance byteSize9 :: ByteSize 9 +--instance byteSize10 :: ByteSize 10 +--instance byteSize11 :: ByteSize 11 +--instance byteSize12 :: ByteSize 12 +--instance byteSize13 :: ByteSize 13 +--instance byteSize14 :: ByteSize 14 +--instance byteSize15 :: ByteSize 15 +--instance byteSize16 :: ByteSize 16 +--instance byteSize17 :: ByteSize 17 +--instance byteSize18 :: ByteSize 18 +--instance byteSize19 :: ByteSize 19 +--instance byteSize20 :: ByteSize 20 +--instance byteSize21 :: ByteSize 21 +--instance byteSize22 :: ByteSize 22 +--instance byteSize23 :: ByteSize 23 +--instance byteSize24 :: ByteSize 24 +--instance byteSize25 :: ByteSize 25 +--instance byteSize26 :: ByteSize 26 +--instance byteSize27 :: ByteSize 27 +--instance byteSize28 :: ByteSize 28 +--instance byteSize29 :: ByteSize 29 +--instance byteSize30 :: ByteSize 30 +--instance byteSize31 :: ByteSize 31 +--instance byteSize32 :: ByteSize 32 +-- \ No newline at end of file diff --git a/src/Network/Ethereum/Web3/Solidity/UInt.purs b/src/Network/Ethereum/Web3/Solidity/UInt.purs index b2f0f6f..d96699a 100644 --- a/src/Network/Ethereum/Web3/Solidity/UInt.purs +++ b/src/Network/Ethereum/Web3/Solidity/UInt.purs @@ -2,14 +2,16 @@ module Network.Ethereum.Web3.Solidity.UInt ( UIntN , unUIntN , uIntNFromBigNumber + , generator ) where import Prelude +import Control.Monad.Gen (class MonadGen, chooseInt) import Data.Maybe (Maybe(..), fromJust) +import Data.Reflectable (class Reflectable, reflectType) import Network.Ethereum.Core.BigNumber (BigNumber, embed, fromString, pow) import Network.Ethereum.Core.HexString (genBytes, unHex) -import Network.Ethereum.Web3.Solidity.Size (class KnownSize, sizeVal) import Partial.Unsafe (unsafePartial) import Test.QuickCheck (class Arbitrary) import Test.QuickCheck.Gen as Gen @@ -26,9 +28,24 @@ derive newtype instance showUIntN :: Show (UIntN n) derive newtype instance eqUIntN :: Eq (UIntN n) derive newtype instance ordUIntN :: Ord (UIntN n) -instance KnownSize n => Arbitrary (UIntN n) where +generator + :: forall n m + . Reflectable n Int + => MonadGen m + => Proxy n + -> m (UIntN n) +generator p = do + nBytes <- (flip div 8) <$> chooseInt 1 (reflectType p) + bs <- genBytes nBytes + let + a = + if bs == mempty then zero + else unsafePartial $ fromJust $ fromString $ unHex bs + pure $ UIntN $ if a < zero then -a else a + +instance Reflectable n Int => Arbitrary (UIntN n) where arbitrary = do - nBytes <- (flip div 8) <$> Gen.chooseInt 1 (sizeVal (Proxy @n)) + nBytes <- (flip div 8) <$> Gen.chooseInt 1 (reflectType (Proxy @n)) bs <- genBytes nBytes let a = @@ -37,16 +54,16 @@ instance KnownSize n => Arbitrary (UIntN n) where pure $ UIntN $ if a < zero then -a else a -- | Access the raw underlying unsigned integer -unUIntN :: forall n. KnownSize n => UIntN n -> BigNumber +unUIntN :: forall n. UIntN n -> BigNumber unUIntN (UIntN a) = a -- | Attempt to coerce an unsigned integer into a statically sized one. -- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes. -uIntNFromBigNumber :: forall n. KnownSize n => Proxy n -> BigNumber -> Maybe (UIntN n) +uIntNFromBigNumber :: forall n. Reflectable n Int => Proxy n -> BigNumber -> Maybe (UIntN n) uIntNFromBigNumber _ a | a < zero = Nothing | otherwise = let - maxVal = (embed 2) `pow` (sizeVal (Proxy :: Proxy n)) - one + maxVal = (embed 2) `pow` (reflectType (Proxy :: Proxy n)) - one in if a > maxVal then Nothing else Just <<< UIntN $ a diff --git a/src/Network/Ethereum/Web3/Solidity/Vector.purs b/src/Network/Ethereum/Web3/Solidity/Vector.purs index 3ec2918..fb2da15 100644 --- a/src/Network/Ethereum/Web3/Solidity/Vector.purs +++ b/src/Network/Ethereum/Web3/Solidity/Vector.purs @@ -6,19 +6,22 @@ module Network.Ethereum.Web3.Solidity.Vector , (:<) , vectorLength , toVector + , generator ) where import Prelude +import Control.Monad.Gen (class MonadGen) import Data.Array ((:)) import Data.Array as A import Data.Foldable (class Foldable) import Data.Maybe (Maybe(..)) +import Data.Reflectable (class Reflectable, reflectType) import Data.Traversable (class Traversable) -import Data.Unfoldable (class Unfoldable, class Unfoldable1) -import Network.Ethereum.Web3.Solidity.Size (class KnownSize, sizeVal) +import Data.Unfoldable (class Unfoldable, class Unfoldable1, replicateA) import Prim.Int (class Add) import Test.QuickCheck (class Arbitrary, arbitrary) +import Type.Proxy (Proxy(..)) -- | Represents a statically sized vector of length `n`. -- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes. @@ -32,10 +35,14 @@ derive newtype instance unfoldableVector :: Unfoldable (Vector n) derive newtype instance foldableVector :: Foldable (Vector n) derive newtype instance traversableVector :: Traversable (Vector n) -instance Arbitrary (Vector 0 a) where - arbitrary = pure nilVector -else instance (Arbitrary a, Arbitrary (Vector n a), Add n 1 m) => Arbitrary (Vector m a) where - arbitrary = vCons <$> arbitrary <*> arbitrary +generator + :: forall n m proxy a + . Reflectable n Int + => MonadGen m + => proxy n + -> m a + -> m (Vector n a) +generator _ gen = Vector <$> replicateA (reflectType (Proxy @n)) gen -- | Access the underlying array unVector :: forall a n. Vector n a -> Array a @@ -57,9 +64,9 @@ vectorLength (Vector as) = A.length as -- | Attempt to coerce an array into a statically sized array. -- | See module [Network.Ethereum.Web3.Solidity.Sizes](/Network.Ethereum.Web3.Solidity.Sizes) for some predefined sizes. -toVector :: forall a (n :: Int) proxy. KnownSize n => proxy n -> Array a -> Maybe (Vector n a) -toVector proxy as = - if sizeVal proxy /= A.length as then +toVector :: forall a (n :: Int) proxy. Reflectable n Int => proxy n -> Array a -> Maybe (Vector n a) +toVector _ as = + if reflectType (Proxy @n) /= A.length as then Nothing else Just (Vector as) diff --git a/test/web3/Web3Spec/Encoding/ContainersSpec.purs b/test/web3/Web3Spec/Encoding/ContainersSpec.purs index 4f8856b..96338bd 100644 --- a/test/web3/Web3Spec/Encoding/ContainersSpec.purs +++ b/test/web3/Web3Spec/Encoding/ContainersSpec.purs @@ -3,242 +3,41 @@ module Web3Spec.Encoding.ContainersSpec (spec) where import Prelude import Control.Monad.Gen (chooseInt, frequency, suchThat) -import Data.Array (foldMap) -import Data.ByteString as BS +import Data.Array (filter, foldMap, (..)) +import Data.Array.NonEmpty (NonEmptyArray, fromArray) +import Data.Array.NonEmpty as NEA import Data.Either (Either(..)) import Data.Enum (toEnumWithDefaults) -import Data.Generic.Rep (class Generic) +import Data.Foldable (for_) import Data.Int (toNumber) import Data.Maybe (fromJust) import Data.NonEmpty (NonEmpty(..)) +import Data.Reflectable (reifyType) import Data.String (CodePoint, fromCodePointArray) import Data.Tuple (Tuple(..)) -import Effect.Aff (Aff) import Effect.Class (liftEffect) import Network.Ethereum.Core.HexString (toByteString) -import Network.Ethereum.Web3.Solidity (BytesN, IntN, Tuple1(..), Tuple2(..), Tuple4(..), Tuple9(..), UIntN, fromByteString, intNFromBigNumber, nilVector, uIntNFromBigNumber, (:<)) import Network.Ethereum.Web3.Solidity.AbiEncoding (class ABIEncode, class ABIDecode, toDataBuilder, fromData) -import Network.Ethereum.Web3.Solidity.Generic (genericFromData, genericABIEncode, class GenericABIDecode, class GenericABIEncode) -import Network.Ethereum.Web3.Solidity.Sizes (s1, s16, s2, s224, s256, s4) -import Network.Ethereum.Web3.Solidity.Vector (Vector, toVector) -import Network.Ethereum.Web3.Types (Address, HexString, embed, mkAddress, mkHexString) +import Network.Ethereum.Web3.Solidity.Bytes as BytesN +import Network.Ethereum.Web3.Solidity.EncodingType (class EncodingType) +import Network.Ethereum.Web3.Solidity.Int as IntN +import Network.Ethereum.Web3.Solidity.UInt as UIntN +import Network.Ethereum.Web3.Solidity.Vector as Vector +import Network.Ethereum.Web3.Types (Address, HexString) import Parsing (ParseError) import Partial.Unsafe (unsafePartial) -import Test.QuickCheck (class Arbitrary, arbitrary, quickCheck, (===)) -import Test.QuickCheck.Gen (arrayOf) +import Test.QuickCheck (class Arbitrary, arbitrary, quickCheck, quickCheckGen, (===)) +import Test.QuickCheck.Gen (Gen, arrayOf) import Test.Spec (Spec, describe, it) -import Test.Spec.Assertions (shouldEqual) spec :: Spec Unit spec = describe "encoding-spec for containers" do - staticArraysTests - dynamicArraysTests - tuplesTest typePropertyTests arrayTypePropertyTests vecTypePropertyTests nestedTypePropertyTests -roundTrip :: forall a. Show a => Eq a => ABIEncode a => ABIDecode a => a -> HexString -> Aff Unit -roundTrip decoded encoded = do - encoded `shouldEqual` toDataBuilder decoded - fromData encoded `shouldEqual` Right decoded - -roundTripGeneric - :: forall a rep - . Show a - => Eq a - => Generic a rep - => GenericABIEncode rep - => GenericABIDecode rep - => a - -> HexString - -> Aff Unit -roundTripGeneric decoded encoded = do - encoded `shouldEqual` genericABIEncode decoded - genericFromData encoded `shouldEqual` Right decoded - -staticArraysTests :: Spec Unit -staticArraysTests = - describe "statically sized array tests" do - it "can encode statically sized vectors of addresses" do - let - mgivenElement = toVector s1 $ [ false ] - - givenElement = (unsafePartial fromJust $ mgivenElement) - - given = (unsafePartial fromJust $ toVector s2 [ givenElement, givenElement ]) - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000000" - <> "0000000000000000000000000000000000000000000000000000000000000000" - roundTrip given expected - it "can encode statically sized vectors of statically sized vectors of type bool" do - let - mgiven = - toVector s2 - $ map (\a -> unsafePartial fromJust $ mkAddress =<< mkHexString a) - [ "407d73d8a49eeb85d32cf465507dd71d507100c1" - , "407d73d8a49eeb85d32cf465507dd71d507100c3" - ] - - given = (unsafePartial $ fromJust $ mgiven) :: Vector 2 Address - - expected = - unsafePartial (fromJust <<< mkHexString) $ "000000000000000000000000407d73d8a49eeb85d32cf465507dd71d507100c1" - <> "000000000000000000000000407d73d8a49eeb85d32cf465507dd71d507100c3" - roundTrip given expected - it "can encode statically sized vectors of statically sized bytes" do - let - elem1 = unsafePartial fromJust (fromByteString s1 =<< flip BS.fromString BS.Hex "cf") - - elem2 = unsafePartial fromJust (fromByteString s1 =<< flip BS.fromString BS.Hex "68") - - elem3 = unsafePartial fromJust (fromByteString s1 =<< flip BS.fromString BS.Hex "4d") - - elem4 = unsafePartial fromJust (fromByteString s1 =<< flip BS.fromString BS.Hex "fb") - - given = unsafePartial fromJust (toVector s4 $ [ elem1, elem2, elem3, elem4 ]) :: Vector 4 (BytesN 1) - - expected = - unsafePartial (fromJust <<< mkHexString) - $ "cf00000000000000000000000000000000000000000000000000000000000000" - <> "6800000000000000000000000000000000000000000000000000000000000000" - <> "4d00000000000000000000000000000000000000000000000000000000000000" - <> "fb00000000000000000000000000000000000000000000000000000000000000" - roundTrip given expected - -dynamicArraysTests :: Spec Unit -dynamicArraysTests = - describe "dynamically sized array tests" do - it "can encode dynamically sized lists of bools" do - let - given = [ true, true, false ] - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000003" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000000" - roundTrip given expected - -tuplesTest :: Spec Unit -tuplesTest = - describe "tuples test" do - it "can encode 2-tuples with both static args" do - let - given = Tuple2 true false - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000000" - roundTripGeneric given expected - it "can encode 1-tuples with dynamic arg" do - let - given = Tuple1 [ true, false ] - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000020" - <> "0000000000000000000000000000000000000000000000000000000000000002" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000000" - roundTripGeneric given expected - it "can encode 4-tuples with a mix of args -- (UInt, String, Boolean, Array Int)" do - let - given = Tuple4 1 "dave" true [ 1, 2, 3 ] - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000080" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "00000000000000000000000000000000000000000000000000000000000000c0" - <> "0000000000000000000000000000000000000000000000000000000000000004" - <> "6461766500000000000000000000000000000000000000000000000000000000" - <> "0000000000000000000000000000000000000000000000000000000000000003" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000002" - <> "0000000000000000000000000000000000000000000000000000000000000003" - roundTripGeneric given expected - it "can do something really complicated" do - let - uint = unsafePartial $ fromJust $ uIntNFromBigNumber s256 $ embed 1 - - int = unsafePartial $ fromJust $ intNFromBigNumber s256 $ embed $ negate 1 - - bool = true - - int224 = unsafePartial $ fromJust $ intNFromBigNumber s224 $ embed 221 - - bools = true :< false :< nilVector - - ints = - [ unsafePartial $ fromJust $ intNFromBigNumber s256 $ embed 1 - , unsafePartial $ fromJust $ intNFromBigNumber s256 $ embed $ negate 1 - , unsafePartial $ fromJust $ intNFromBigNumber s256 $ embed 3 - ] - - string = "hello" - - bytes16 = unsafePartial fromJust $ fromByteString s16 =<< flip BS.fromString BS.Hex "12345678123456781234567812345678" - - elem = unsafePartial fromJust $ fromByteString s2 =<< flip BS.fromString BS.Hex "1234" - - vector4 = elem :< elem :< elem :< elem :< nilVector - - bytes2s = [ vector4, vector4 ] - - given = - Tuple9 uint int bool int224 bools ints string bytes16 bytes2s - :: Tuple9 (UIntN 256) - (IntN 256) - Boolean - (IntN 224) - (Vector 2 Boolean) - (Array (IntN 256)) - String - (BytesN 16) - (Array (Vector 4 (BytesN 2))) - - expected = - unsafePartial fromJust <<< mkHexString $ "0000000000000000000000000000000000000000000000000000000000000001" - <> "ffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "00000000000000000000000000000000000000000000000000000000000000dd" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "0000000000000000000000000000000000000000000000000000000000000000" - <> "0000000000000000000000000000000000000000000000000000000000000140" - <> "00000000000000000000000000000000000000000000000000000000000001c0" - <> "1234567812345678123456781234567800000000000000000000000000000000" - <> "0000000000000000000000000000000000000000000000000000000000000200" - <> "0000000000000000000000000000000000000000000000000000000000000003" - <> "0000000000000000000000000000000000000000000000000000000000000001" - <> "ffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff" - <> "0000000000000000000000000000000000000000000000000000000000000003" - <> "0000000000000000000000000000000000000000000000000000000000000005" - <> "68656c6c6f000000000000000000000000000000000000000000000000000000" - <> "0000000000000000000000000000000000000000000000000000000000000002" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - <> "1234000000000000000000000000000000000000000000000000000000000000" - roundTripGeneric given expected - -encodeDecodeGeneric - :: forall a rep - . Show a - => Eq a - => Generic a rep - => GenericABIEncode rep - => GenericABIDecode rep - => a - -> Either ParseError a -encodeDecodeGeneric x = genericFromData $ genericABIEncode x - encodeDecode :: forall a . Show a @@ -253,217 +52,204 @@ encodeDecode x = in (fromData a) ---tuplePropertyTests :: Spec Unit ---tuplePropertyTests = --- describe "Tuple property tests" do --- it "can encode and decode a Tuple1" $ liftEffect $ do --- quickCheck \(x :: Tuple1 Int) -> - typePropertyTests :: Spec Unit typePropertyTests = describe "Type property tests" do - it "can encode and decode a string" $ liftEffect $ do - quickCheck \(BMPString x) -> (encodeDecode x) === Right x - it "can encode and decode a bytestring" $ liftEffect $ do + it "can encode/decode a string" $ liftEffect $ do + quickCheck \(x :: BMPString) -> (encodeDecode x) === Right x + + it "can encode/decode bytestring" $ liftEffect $ do quickCheck \(_x :: HexString) -> let x = toByteString _x in (encodeDecode x) === Right x - it "can encode and decode a bool" $ liftEffect $ do + + it "can encode/decode bool" $ liftEffect $ do quickCheck \(x :: Boolean) -> encodeDecode x === Right x - it "can encode and decode an address" $ liftEffect $ do + + it "can encode/decode address" $ liftEffect $ do quickCheck \(x :: Address) -> encodeDecode x === Right x - it "can encode and decode an int8" $ liftEffect $ do - quickCheck \(x :: IntN 8) -> encodeDecode x === Right x - it "can encode and decode an int16" $ liftEffect $ do - quickCheck \(x :: IntN 16) -> encodeDecode x === Right x - it "can encode and decode an int32" $ liftEffect $ do - quickCheck \(x :: IntN 32) -> encodeDecode x === Right x - it "can encode and decode an int64" $ liftEffect $ do - quickCheck \(x :: IntN 64) -> encodeDecode x === Right x - it "can encode and decode an int128" $ liftEffect $ do - quickCheck \(x :: IntN 128) -> encodeDecode x === Right x - it "can encode and decode an int256" $ liftEffect $ do - quickCheck \(x :: IntN 256) -> encodeDecode x === Right x - it "can encode and decode an uint8" $ liftEffect $ do - quickCheck \(x :: UIntN 8) -> encodeDecode x === Right x - it "can encode and decode an uint16" $ liftEffect $ do - quickCheck \(x :: UIntN 16) -> encodeDecode x === Right x - it "can encode and decode an uint32" $ liftEffect $ do - quickCheck \(x :: UIntN 32) -> encodeDecode x === Right x - it "can encode and decode an uint64" $ liftEffect $ do - quickCheck \(x :: UIntN 64) -> encodeDecode x === Right x - it "can encode and decode an uint128" $ liftEffect $ do - quickCheck \(x :: UIntN 128) -> encodeDecode x === Right x - it "can encode and decode an uint256" $ liftEffect $ do - quickCheck \(x :: UIntN 256) -> encodeDecode x === Right x - it "can encode and decode bytes1" $ liftEffect $ do - quickCheck \(x :: BytesN 1) -> encodeDecode x === Right x - it "can encode and decode bytes2" $ liftEffect $ do - quickCheck \(x :: BytesN 2) -> encodeDecode x === Right x - it "can encode and decode bytes3" $ liftEffect $ do - quickCheck \(x :: BytesN 3) -> encodeDecode x === Right x - it "can encode and decode bytes4" $ liftEffect $ do - quickCheck \(x :: BytesN 4) -> encodeDecode x === Right x - it "can encode and decode bytes5" $ liftEffect $ do - quickCheck \(x :: BytesN 5) -> encodeDecode x === Right x - it "can encode and decode bytes6" $ liftEffect $ do - quickCheck \(x :: BytesN 6) -> encodeDecode x === Right x - it "can encode and decode bytes7" $ liftEffect $ do - quickCheck \(x :: BytesN 7) -> encodeDecode x === Right x - it "can encode and decode bytes8" $ liftEffect $ do - quickCheck \(x :: BytesN 8) -> encodeDecode x === Right x - it "can encode and decode bytes9" $ liftEffect $ do - quickCheck \(x :: BytesN 9) -> encodeDecode x === Right x - it "can encode and decode bytes10" $ liftEffect $ do - quickCheck \(x :: BytesN 10) -> encodeDecode x === Right x - it "can encode and decode bytes11" $ liftEffect $ do - quickCheck \(x :: BytesN 11) -> encodeDecode x === Right x - it "can encode and decode bytes12" $ liftEffect $ do - quickCheck \(x :: BytesN 12) -> encodeDecode x === Right x - it "can encode and decode bytes13" $ liftEffect $ do - quickCheck \(x :: BytesN 13) -> encodeDecode x === Right x - it "can encode and decode bytes14" $ liftEffect $ do - quickCheck \(x :: BytesN 14) -> encodeDecode x === Right x - it "can encode and decode bytes15" $ liftEffect $ do - quickCheck \(x :: BytesN 15) -> encodeDecode x === Right x - it "can encode and decode bytes16" $ liftEffect $ do - quickCheck \(x :: BytesN 16) -> encodeDecode x === Right x - it "can encode and decode bytes17" $ liftEffect $ do - quickCheck \(x :: BytesN 17) -> encodeDecode x === Right x - it "can encode and decode bytes18" $ liftEffect $ do - quickCheck \(x :: BytesN 18) -> encodeDecode x === Right x - it "can encode and decode bytes19" $ liftEffect $ do - quickCheck \(x :: BytesN 19) -> encodeDecode x === Right x - it "can encode and decode bytes20" $ liftEffect $ do - quickCheck \(x :: BytesN 20) -> encodeDecode x === Right x - it "can encode and decode bytes21" $ liftEffect $ do - quickCheck \(x :: BytesN 21) -> encodeDecode x === Right x - it "can encode and decode bytes22" $ liftEffect $ do - quickCheck \(x :: BytesN 22) -> encodeDecode x === Right x - it "can encode and decode bytes23" $ liftEffect $ do - quickCheck \(x :: BytesN 23) -> encodeDecode x === Right x - it "can encode and decode bytes24" $ liftEffect $ do - quickCheck \(x :: BytesN 24) -> encodeDecode x === Right x - it "can encode and decode bytes25" $ liftEffect $ do - quickCheck \(x :: BytesN 25) -> encodeDecode x === Right x - it "can encode and decode bytes26" $ liftEffect $ do - quickCheck \(x :: BytesN 26) -> encodeDecode x === Right x - it "can encode and decode bytes27" $ liftEffect $ do - quickCheck \(x :: BytesN 27) -> encodeDecode x === Right x - it "can encode and decode bytes28" $ liftEffect $ do - quickCheck \(x :: BytesN 28) -> encodeDecode x === Right x - it "can encode and decode bytes29" $ liftEffect $ do - quickCheck \(x :: BytesN 29) -> encodeDecode x === Right x - it "can encode and decode bytes30" $ liftEffect $ do - quickCheck \(x :: BytesN 30) -> encodeDecode x === Right x - it "can encode and decode bytes31" $ liftEffect $ do - quickCheck \(x :: BytesN 31) -> encodeDecode x === Right x - it "can encode and decode bytes32" $ liftEffect $ do - quickCheck \(x :: BytesN 32) -> encodeDecode x === Right x + + it "can encode/decode intN" $ liftEffect $ do + for_ intSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- IntN.generator p + pure $ encodeDecode x === Right x + + it "can encode/decode uintN" $ liftEffect $ do + for_ intSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- UIntN.generator p + pure $ encodeDecode x === Right x + + it "can encode/decode bytesN" $ liftEffect $ do + for_ bytesSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- BytesN.generator p + pure $ encodeDecode x === Right x + + it "can encode/decode string" $ liftEffect $ do + quickCheck \(x :: BMPString) -> encodeDecode x === Right x arrayTypePropertyTests :: Spec Unit arrayTypePropertyTests = do - describe "Array type property tests: int" do - it "Can do arrays of int8" $ liftEffect do - quickCheck $ \(x :: Array (IntN 8)) -> encodeDecode x === Right x - it "Can do arrays of int32" $ liftEffect do - quickCheck $ \(x :: Array (IntN 32)) -> encodeDecode x === Right x - it "Can do arrays of int256" $ liftEffect do - quickCheck $ \(x :: Array (IntN 256)) -> encodeDecode x === Right x - - describe "Array type property tests: uint" do - it "Can do arrays of uint16" $ liftEffect do - quickCheck $ \(x :: Array (UIntN 16)) -> encodeDecode x === Right x - it "Can do arrays of uint24" $ liftEffect do - quickCheck $ \(x :: Array (UIntN 24)) -> encodeDecode x === Right x - it "Can do arrays of uint64" $ liftEffect do - quickCheck $ \(x :: Array (UIntN 64)) -> encodeDecode x === Right x - - describe "Array type property tests: address" do - it "Can do arrays of address" $ liftEffect do + + describe "Array type property tests" do + + it "Can encode/decode intN[]" $ liftEffect do + for_ intSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- arrayOf (IntN.generator p) + pure $ encodeDecode x === Right x + + it "Can encode/decode uintN[]" $ liftEffect do + for_ intSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- arrayOf (UIntN.generator p) + pure $ encodeDecode x === Right x + + it "Can encode/decode bytesN[]" $ liftEffect do + for_ bytesSizes $ \n -> quickCheckGen $ do + reifyType n \p -> do + x <- arrayOf (BytesN.generator p) + pure $ encodeDecode x === Right x + + it "Can encode/decode address[]" $ liftEffect do quickCheck $ \(x :: Address) -> encodeDecode x === Right x - describe "Array type property tests: string" do - it "Can do arrays of address" $ liftEffect do - quickCheck $ \(_x :: Array BMPString) -> - let - x = map (\(BMPString s) -> s) _x - in - encodeDecode x === Right x + it "Can encode/decode string[]" $ liftEffect do + quickCheck $ \(x :: Array BMPString) -> + encodeDecode x === Right x vecTypePropertyTests :: Spec Unit vecTypePropertyTests = do - describe "Vec type property tests: int[N]" do - it "Can do vec of int40[1]" $ liftEffect do - quickCheck $ \(x :: Vector 1 (IntN 40)) -> encodeDecode x === Right x - it "Can do vec of int112[5]" $ liftEffect do - quickCheck $ \(x :: Vector 5 (IntN 112)) -> encodeDecode x === Right x - it "Can do vec of int168[10]" $ liftEffect do - quickCheck $ \(x :: Vector 10 (IntN 168)) -> encodeDecode x === Right x - - describe "Array type property tests: uint[N]" do - it "Can do vec of uint16" $ liftEffect do - quickCheck $ \(x :: Vector 2 (UIntN 144)) -> encodeDecode x === Right x - it "Can do vec of uint24" $ liftEffect do - quickCheck $ \(x :: Vector 4 (UIntN 176)) -> encodeDecode x === Right x - it "Can do vec of uint24" $ liftEffect do - quickCheck $ \(x :: Vector 7 (UIntN 192)) -> encodeDecode x === Right x - - describe "Array type property tests: address[N]" do - it "Can do vec of address" $ liftEffect do - quickCheck $ \(x :: Vector 3 Address) -> encodeDecode x === Right x - it "Can do vec of address" $ liftEffect do - quickCheck $ \(x :: Vector 6 Address) -> encodeDecode x === Right x - - describe "Array type property tests: string[N]" do - it "Can do vec of address" $ liftEffect do - quickCheck $ \(_x :: Vector 3 BMPString) -> - let - x = map (\(BMPString s) -> s) _x - in - encodeDecode x === Right x - it "Can do vec of string" $ liftEffect do - quickCheck $ \(_x :: Vector 4 BMPString) -> - let - x = map (\(BMPString s) -> s) _x - in - encodeDecode x === Right x + + describe "Vector type property tests" do + + it "Can encode/decode intN[k]" $ liftEffect do + for_ intSizes $ \n -> + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> + reifyType n \pn -> do + x <- Vector.generator pk (IntN.generator pn) + pure $ encodeDecode x === Right x + + it "Can encode/decode uintN[k]" $ liftEffect do + for_ intSizes $ \n -> + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> + reifyType n \pn -> do + x <- Vector.generator pk (UIntN.generator pn) + pure $ encodeDecode x === Right x + + it "Can encode/decode bytesN[k]" $ liftEffect do + for_ bytesSizes $ \n -> + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> + reifyType n \pn -> do + x <- Vector.generator pk (BytesN.generator pn) + pure $ encodeDecode x === Right x + + it "Can encode/decode address[k]" $ liftEffect do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> do + x <- Vector.generator pk (arbitrary :: Gen Address) + pure $ encodeDecode x === Right x + + it "Can encode/decode string[k]" $ liftEffect do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> do + x <- Vector.generator pk (arbitrary :: Gen BMPString) + pure $ encodeDecode x === Right x nestedTypePropertyTests :: Spec Unit nestedTypePropertyTests = do - describe "Nested type property tests for fixed size things" do - it "Can do address[4][]" $ liftEffect do - quickCheck \(x :: Array (Vector 4 Address)) -> encodeDecode x === Right x - it "Can do int64[][5]" $ liftEffect do - quickCheck \(x :: Vector 4 (IntN 64)) -> encodeDecode x === Right x - it "Can do uint[3][4]" $ liftEffect do - quickCheck \(x :: Vector 4 (Vector 3 (UIntN 256))) -> encodeDecode x === Right x - it "Can do bytes12[][]" $ liftEffect do - quickCheck \(x :: Array (Array (BytesN 32))) -> encodeDecode x === Right x - - describe "Nested type property tests for variable size things" do - it "Can do string[4][]" $ liftEffect do - quickCheck \(x :: Array (Vector 4 String)) -> encodeDecode x === Right x - it "Can do bytes[][5]" $ liftEffect do - quickCheck \(_x :: Vector 4 (Array HexString)) -> - let - x = map (map toByteString) _x - in - encodeDecode x === Right x - it "Can do string[2][5]" $ liftEffect do - quickCheck \(x :: Vector 5 (Vector 2 String)) -> encodeDecode x === Right x - it "Can do bytes[][]" $ liftEffect do - quickCheck \(_x :: Array (Array HexString)) -> - let - x = map (map toByteString) _x - in - encodeDecode x === Right x + describe "Nested type property tests for vector, vector" do + + it "Can encode/decode bytesN[k1][k2]" $ liftEffect do + for_ bytesSizes $ \n -> do + quickCheckGen $ do + k1 <- chooseInt 1 10 + k2 <- chooseInt 1 10 + reifyType k1 \pk1 -> + reifyType k2 \pk2 -> + reifyType n \pn -> do + x <- Vector.generator pk2 (Vector.generator pk1 (BytesN.generator pn)) + pure $ encodeDecode x === Right x + + it "Can encode/decode string[k1][k2]" $ liftEffect do + quickCheckGen $ do + k1 <- chooseInt 1 10 + k2 <- chooseInt 1 10 + reifyType k1 \pk1 -> + reifyType k2 \pk2 -> do + x <- Vector.generator pk2 (Vector.generator pk1 (arbitrary :: Gen BMPString)) + pure $ encodeDecode x === Right x + + describe "Nested type property tests for array, vector" do + + it "Can encode/decode bytesN[k][]" $ liftEffect do + for_ bytesSizes $ \n -> do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> + reifyType n \pn -> do + x <- arrayOf (Vector.generator pk (BytesN.generator pn)) + pure $ encodeDecode x === Right x + + it "Can encode/decode string[k][]" $ liftEffect do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> do + x <- arrayOf (Vector.generator pk (arbitrary :: Gen BMPString)) + pure $ encodeDecode x === Right x + + describe "Nested type property tests for vector, array" do + + it "Can encode/decode uintN[][k]" $ liftEffect do + for_ intSizes $ \n -> do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> + reifyType n \pn -> do + x <- (Vector.generator pk (arrayOf $ UIntN.generator pn)) + pure $ encodeDecode x === Right x + + it "Can encode/decode string[][k]" $ liftEffect do + quickCheckGen $ do + k <- chooseInt 1 10 + reifyType k \pk -> do + x <- (Vector.generator pk (arrayOf (arbitrary :: Gen BMPString))) + pure $ encodeDecode x === Right x + + describe "Nested type property tests for array, array" do + + it "Can encode/decode intN[][]" $ liftEffect do + for_ intSizes $ \n -> do + quickCheckGen $ + reifyType n \pn -> do + x <- (arrayOf (arrayOf $ IntN.generator pn)) + pure $ encodeDecode x === Right x + + it "Can encode/decode string[][]" $ liftEffect do + quickCheck \(x :: Array (Array BMPString)) -> + encodeDecode x === Right x -------------------------------------------------------------------------------- newtype BMPString = BMPString String +derive newtype instance Eq BMPString +derive newtype instance Show BMPString +derive newtype instance ABIDecode BMPString +derive newtype instance ABIEncode BMPString +derive newtype instance EncodingType BMPString + data UnicodeChar = Normal CodePoint | Surrogates CodePoint CodePoint instance Arbitrary BMPString where @@ -491,4 +277,12 @@ instance Arbitrary UnicodeChar where chooseInt 0 maxCP `suchThat` \n -> (n < hiLB || n > hiUB) && (n < loLB || n > loUB) -- probability that you pick a surrogate from all possible codepoints - p = toNumber ((hiUB - hiLB + 1) + (loUB - loLB + 1)) / toNumber (maxCP + 1) \ No newline at end of file + p = toNumber ((hiUB - hiLB + 1) + (loUB - loLB + 1)) / toNumber (maxCP + 1) + +intSizes :: NonEmptyArray Int +intSizes = unsafePartial fromJust + $ fromArray + $ filter (\x -> x `mod` 8 == 0) (8 .. 256) + +bytesSizes :: NonEmptyArray Int +bytesSizes = 1 NEA... 32 diff --git a/test/web3/Web3Spec/Live/Utils.purs b/test/web3/Web3Spec/Live/Utils.purs index 62f4b1f..456f228 100644 --- a/test/web3/Web3Spec/Live/Utils.purs +++ b/test/web3/Web3Spec/Live/Utils.purs @@ -10,6 +10,7 @@ import Data.Either (Either(..)) import Data.Lens ((?~)) import Data.Maybe (Maybe(..), fromJust) import Data.Newtype (wrap, unwrap) +import Data.Reflectable (class Reflectable) import Data.Traversable (intercalate) import Data.Tuple (Tuple(..)) import Effect.Aff (Aff, Milliseconds(..), Fiber, joinFiber, delay) @@ -18,7 +19,7 @@ import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class.Console as C import Network.Ethereum.Core.BigNumber (decimal, fromStringAs) import Network.Ethereum.Core.Signatures (mkAddress) -import Network.Ethereum.Web3 (class EventFilter, class KnownSize, Address, Web3Error, BigNumber, BlockNumber, BytesN, CallError, EventAction(..), HexString, Provider, TransactionOptions, TransactionReceipt(..), TransactionStatus(..), UIntN, Web3, _from, _gas, defaultTransactionOptions, event, embed, eventFilter, forkWeb3', fromByteString, intNFromBigNumber, mkHexString, runWeb3, uIntNFromBigNumber) +import Network.Ethereum.Web3 (class EventFilter, Address, Web3Error, BigNumber, BlockNumber, BytesN, CallError, EventAction(..), HexString, Provider, TransactionOptions, TransactionReceipt(..), TransactionStatus(..), UIntN, Web3, _from, _gas, defaultTransactionOptions, event, embed, eventFilter, forkWeb3', fromByteString, intNFromBigNumber, mkHexString, runWeb3, uIntNFromBigNumber) import Network.Ethereum.Web3.Api as Api import Network.Ethereum.Web3.Solidity (class DecodeEvent, IntN) import Network.Ethereum.Web3.Types (NoPay) @@ -185,7 +186,7 @@ mkHexString' hx = unsafePartial fromJust $ mkHexString hx mkUIntN :: forall n - . KnownSize n + . Reflectable n Int => Proxy n -> Int -> UIntN n @@ -193,7 +194,7 @@ mkUIntN p n = unsafePartial fromJust $ uIntNFromBigNumber p $ embed n mkIntN :: forall n - . KnownSize n + . Reflectable n Int => Proxy n -> Int -> IntN n @@ -201,7 +202,7 @@ mkIntN p n = unsafePartial fromJust $ intNFromBigNumber p $ embed n mkBytesN :: forall n - . KnownSize n + . Reflectable n Int => Proxy n -> String -> BytesN n