Skip to content

Commit

Permalink
Use Quickcheck for property based testing (#168)
Browse files Browse the repository at this point in the history
* use new BigNumber rep

* tests passing

* added many property based tests

* remove size restrictions on tests

* use reifyType to cover literally every possible case

* finish cleaning up tests

* test coverage

* upgrade tests

* no local deps

* remove unused import

* remove arb tuples

* rename embed to fromInt, add laws checks for value

* update js-bigint

* update eth-core
  • Loading branch information
martyall authored Sep 18, 2023
1 parent eec2556 commit b1516ad
Show file tree
Hide file tree
Showing 26 changed files with 857 additions and 1,057 deletions.
1 change: 0 additions & 1 deletion package.json
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@
"test": "spago -x test.dhall test"
},
"dependencies": {
"bn.js": "^4.11.0",
"ethjs-provider-http": "^0.1.6",
"keccak": "^1.0.2",
"rlp": "^2.0.0",
Expand Down
3 changes: 3 additions & 0 deletions packages.dhall
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
let upstream =
https://raw.githubusercontent.com/f-o-a-m/package-sets/09b71674a327f7601276846c1afb537342bb57ff/purs-0.15.7-web3.dhall
sha256:7e32f0c65a7b5d334ee98d7fda1d7d3a557b6b478421f545694bd8e1cd4d16ac
with eth-core.version = "v10.0.0"
with js-bigints.version = "v2.2.0"


let overrides = {=}

Expand Down
1 change: 1 addition & 0 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@
, "foreign"
, "foreign-object"
, "fork"
, "gen"
, "heterogeneous"
, "maybe"
, "newtype"
Expand Down
8 changes: 2 additions & 6 deletions src/Network/Ethereum/Web3.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -31,5 +27,5 @@ import Network.Ethereum.Web3.Solidity
, vCons
, (:<)
)
import Network.Ethereum.Web3.Types (forkWeb3, forkWeb3', runWeb3, Address, Babbage, BigNumber, Block(..), BlockNumber(..), ChainCursor(..), Change(..), Ether, EventAction(..), Filter, FilterId, Finney, HexString, KEther, Lovelace, CallError(..), Shannon, Szabo, Transaction(..), TransactionOptions(..), TransactionReceipt(..), TransactionStatus(..), Value, Web3, Web3Par, Web3Error(..), Wei, _address, _data, _from, _fromBlock, _gas, _gasPrice, _nonce, _to, _toBlock, _topics, _value, convert, defaultFilter, defaultTransactionOptions, embed, formatValue, fromMinorUnit, mkAddress, mkHexString, mkValue, toMinorUnit, throwWeb3, unAddress, unHex)
import Network.Ethereum.Web3.Types (forkWeb3, forkWeb3', runWeb3, Address, Babbage, BigNumber, Block(..), BlockNumber(..), ChainCursor(..), Change(..), Ether, EventAction(..), Filter, FilterId, Finney, HexString, KEther, Lovelace, CallError(..), Shannon, Szabo, Transaction(..), TransactionOptions(..), TransactionReceipt(..), TransactionStatus(..), Value, Web3, Web3Par, Web3Error(..), Wei, _address, _data, _from, _fromBlock, _gas, _gasPrice, _nonce, _to, _toBlock, _topics, _value, convert, defaultFilter, defaultTransactionOptions, fromInt, formatValue, fromMinorUnit, mkAddress, mkHexString, mkValue, toMinorUnit, throwWeb3, unAddress, unHex)
import Network.Ethereum.Web3.Types.Provider (Provider, httpProvider, metamaskProvider)
8 changes: 4 additions & 4 deletions src/Network/Ethereum/Web3/Contract/Events.purs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ import Effect.Aff (delay, Milliseconds(..))
import Effect.Aff.Class (liftAff)
import Heterogeneous.Folding (class FoldingWithIndex, class FoldlRecord, hfoldlWithIndex)
import Heterogeneous.Mapping (class MapRecordWithIndex, class Mapping, ConstMapping, hmap)
import Network.Ethereum.Core.BigNumber (BigNumber, embed)
import Network.Ethereum.Core.BigNumber (BigNumber, fromInt)
import Network.Ethereum.Core.HexString (HexString)
import Network.Ethereum.Web3.Api (eth_blockNumber, eth_getFilterChanges, eth_getLogs, eth_newFilter, eth_uninstallFilter)
import Network.Ethereum.Web3.Solidity.Event (class DecodeEvent, decodeEvent)
Expand Down Expand Up @@ -205,20 +205,20 @@ filterProducer cs@(MultiFilterStreamState currentState) = do
-- otherwise try make progress
else case hfoldlWithIndex MultiFilterMinToBlock Latest currentState.filters of
-- consume as many as possible up to the chain head
Latest -> continueTo $ over BlockNumber (_ - embed currentState.trailBy) chainHead
Latest -> continueTo $ over BlockNumber (_ - fromInt currentState.trailBy) chainHead
-- if the original fitler ends at a specific block, consume as many as possible up to that block
-- or terminate if we're already past it
BN targetEnd ->
let
targetEnd' = min targetEnd $ over BlockNumber (_ - embed currentState.trailBy) chainHead
targetEnd' = min targetEnd $ over BlockNumber (_ - fromInt currentState.trailBy) chainHead
in
if currentState.currentBlock <= targetEnd' then
continueTo targetEnd'
else
pure cs
where
newTo :: BlockNumber -> BlockNumber -> Int -> BlockNumber
newTo upper current window = min upper $ over BlockNumber (_ + embed window) current
newTo upper current window = min upper $ over BlockNumber (_ + fromInt window) current

succ :: BlockNumber -> BlockNumber
succ = over BlockNumber (_ + one)
Expand Down
9 changes: 1 addition & 8 deletions src/Network/Ethereum/Web3/Solidity.purs
Original file line number Diff line number Diff line change
@@ -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
Expand All @@ -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
Expand Down
132 changes: 69 additions & 63 deletions src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs
Original file line number Diff line number Diff line change
@@ -1,29 +1,42 @@
module Network.Ethereum.Web3.Solidity.AbiEncoding where
module Network.Ethereum.Web3.Solidity.AbiEncoding
( bytesBuilder
, class ABIDecode
, fromDataParser
, class ABIEncode
, toDataBuilder
, fromBool
, fromData
, int256HexBuilder
, parseBytes
, toBool
, uInt256HexBuilder
, uInt256HexParser
) where

import Prelude

import Data.Array (cons, fold, foldMap, length)
import Data.Array.Partial (init)
import Data.ByteString (ByteString)
import Data.ByteString (toUTF8, fromUTF8, toString, fromString, length, Encoding(Hex)) as BS
import Data.ByteString (toUTF8, fromUTF8, length) as BS
import Data.Either (Either)
import Data.Functor.Tagged (Tagged, tagged, untagged)
import Data.Maybe (maybe, fromJust)
import Data.String (splitAt)
import Data.Tuple (Tuple(..))
import Data.Maybe (fromJust, maybe)
import Data.Reflectable (class Reflectable, reflectType)
import Data.Traversable (for, scanl)
import Data.Tuple (Tuple(..))
import Data.Unfoldable (replicateA)
import Network.Ethereum.Core.BigNumber (toTwosComplement, unsafeToInt)
import Network.Ethereum.Core.HexString (HexString, Signed(..), mkHexString, numberOfBytes, padLeft, padLeftSigned, padRight, toBigNumber, toBigNumberFromSignedHexString, toSignedHexString, unHex)
import Network.Ethereum.Types (Address, BigNumber, embed, mkAddress, unAddress)
import Network.Ethereum.Core.BigNumber (fromString, fromTwosComplement, toString, toTwosComplement, unsafeToInt)
import Network.Ethereum.Core.HexString (HexString, PadByte(..), fromByteString, mkHexString, numberOfBytes, padLeft, padRight, splitAtByteOffset, toByteString, unHex)
import Network.Ethereum.Types (Address, BigNumber, fromInt, 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 Partial.Unsafe (unsafePartial)
import Parsing (ParseError, Parser, ParseState(..), Position(..), ParserT, fail, getParserT, stateParserT, runParser)
import Parsing.Combinators (lookAhead)
import Partial.Unsafe (unsafeCrashWith, unsafePartial)
import Type.Proxy (Proxy(..))

-- | Class representing values that have an encoding and decoding instance to/from a solidity type.
Expand All @@ -50,13 +63,13 @@ instance abiDecodeBool :: ABIDecode Boolean where
fromDataParser = toBool <$> uInt256HexParser

instance abiEncodeInt :: ABIEncode Int where
toDataBuilder = int256HexBuilder <<< embed
toDataBuilder = int256HexBuilder <<< fromInt

instance abiDecodeInt :: ABIDecode Int where
fromDataParser = unsafeToInt <$> int256HexParser

instance abiEncodeAddress :: ABIEncode Address where
toDataBuilder addr = padLeft <<< unAddress $ addr
toDataBuilder addr = padLeft Zero <<< unAddress $ addr

instance abiDecodeAddress :: ABIDecode Address where
fromDataParser = do
Expand All @@ -65,39 +78,39 @@ instance abiDecodeAddress :: ABIDecode Address where
maybe (fail "Address is 20 bytes, receieved more") pure maddr

instance abiEncodeBytesD :: ABIEncode ByteString where
toDataBuilder bytes = uInt256HexBuilder (embed $ BS.length bytes) <> bytesBuilder bytes
toDataBuilder bytes = uInt256HexBuilder (fromInt $ BS.length bytes) <> bytesBuilder bytes

instance abiDecodeBytesD :: ABIDecode ByteString where
fromDataParser = do
len <- fromDataParser
bytesDecode <<< unHex <$> parseBytes (unsafeToInt len)
toByteString <$> parseBytes (unsafeToInt len)

instance abiEncodeString :: ABIEncode String where
toDataBuilder = toDataBuilder <<< BS.toUTF8

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 <<< bytesDecode <<< unHex $ raw
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
Expand All @@ -107,10 +120,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
Expand All @@ -126,7 +139,7 @@ instance abiDecodeVec :: (EncodingType a, KnownSize n, ABIDecode a) => ABIDecode

instance abiEncodeAray :: (EncodingType a, ABIEncode a) => ABIEncode (Array a) where
toDataBuilder l = do
uInt256HexBuilder (embed $ length l)
uInt256HexBuilder (fromInt $ length l)
<>
if isDynamic (Proxy :: Proxy a) then do
let
Expand All @@ -139,7 +152,7 @@ instance abiEncodeAray :: (EncodingType a, ABIEncode a) => ABIEncode (Array a) w
seed = 32 * length l
in
seed `cons` (unsafePartial $ init $ scanl (+) seed lengths)
foldMap (uInt256HexBuilder <<< embed) offsets <> fold encs
foldMap (uInt256HexBuilder <<< fromInt) offsets <> fold encs
else
foldMap toDataBuilder l

Expand All @@ -159,31 +172,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

Expand All @@ -196,37 +209,41 @@ instance abiDecodeTagged :: ABIDecode a => ABIDecode (Tagged s a) where
--------------------------------------------------------------------------------
-- | Special Builders and Parsers
--------------------------------------------------------------------------------

-- | base16 encode, then utf8 encode, then pad
bytesBuilder :: ByteString -> HexString
bytesBuilder = padRight <<< unsafePartial fromJust <<< mkHexString <<< flip BS.toString BS.Hex

-- | unsafe utfDecode
bytesDecode :: String -> ByteString
bytesDecode s = unsafePartial $ fromJust $ flip BS.fromString BS.Hex s
bytesBuilder = padRight Zero <<< fromByteString

-- | Encode something that is essentaially a signed integer.
int256HexBuilder :: BigNumber -> HexString
int256HexBuilder x =
if x < zero then
int256HexBuilder <<< toTwosComplement $ x
else
padLeftSigned <<< toSignedHexString $ x
let
a = toTwosComplement 256 x
x' =
if a < zero then unsafeCrashWith $ "FUCK " <> show a
else unsafePartial $ fromJust $ mkHexString (toString a)
in
if x < zero then padLeft FF x'
else padLeft Zero x'

-- | Encode something that is essentially an unsigned integer.
uInt256HexBuilder :: BigNumber -> HexString
uInt256HexBuilder x =
let
Signed _ x' = toSignedHexString x
in
padLeft x'
uInt256HexBuilder x = unsafePartial $ fromJust $
padLeft Zero <$> mkHexString (toString x)

-- | Parse as a signed `BigNumber`
int256HexParser :: forall m. Monad m => ParserT HexString m BigNumber
int256HexParser = toBigNumberFromSignedHexString <$> parseBytes 32
int256HexParser = do
bs <- unHex <$> parseBytes 32
a <- maybe (fail $ "Failed to parse bytes as BigNumber " <> bs) pure (fromString bs)
pure $ fromTwosComplement 256 a

-- | Parse an unsigned `BigNumber`
uInt256HexParser :: forall m. Monad m => ParserT HexString m BigNumber
uInt256HexParser = toBigNumber <$> parseBytes 32
uInt256HexParser = do
bs <- unHex <$> parseBytes 32
a <- maybe (fail $ "Failed to parse bytes as BigNumber " <> bs) pure (fromString bs)
pure a

-- | Decode a `Boolean` as a BigNumber
fromBool :: Boolean -> BigNumber
Expand All @@ -238,26 +255,15 @@ toBool bn = not $ bn == zero

-- | Read any number of HexDigits
parseBytes :: forall m. Monad m => Int -> ParserT HexString m HexString
parseBytes n = fold <$> replicateA n parseByte

parseByte :: forall m. Monad m => ParserT HexString m HexString
parseByte = do
parseBytes n = do
ParseState input (Position position) _ <- getParserT
if numberOfBytes input < 1 then
if numberOfBytes input < n then
fail "Unexpected EOF"
else do
let
{ after, before } = splitAt 2 (unHex input)
{ after, before } = splitAtByteOffset n input

unsafeMkHex s = unsafePartial $ fromJust $ mkHexString s

position' = Position $ position { column = position.column + 1 }

let
newState = ParseState (unsafeMkHex after) position' true
ret = unsafeMkHex before
position' = Position $ position { column = position.column + n }

-- equivalent to: do
-- put newState -- ParserT is no longer it's own MonadState and theres no putParserT
-- pure ret
stateParserT $ const (Tuple ret newState)
let newState = ParseState after position' true
stateParserT $ const (Tuple before newState)
Loading

0 comments on commit b1516ad

Please sign in to comment.