Skip to content

Commit

Permalink
added many property based tests
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Sep 13, 2023
1 parent aa58e2b commit 55fc8f0
Show file tree
Hide file tree
Showing 5 changed files with 279 additions and 36 deletions.
32 changes: 13 additions & 19 deletions src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ module Network.Ethereum.Web3.Solidity.AbiEncoding
, fromBool
, fromData
, int256HexBuilder
, parseByte
, parseBytes
, toBool
, uInt256HexBuilder
Expand All @@ -27,8 +26,8 @@ import Data.String (splitAt)
import Data.Traversable (for, scanl)
import Data.Tuple (Tuple(..))
import Data.Unfoldable (replicateA)
import Network.Ethereum.Core.BigNumber (fromString, fromTwosComplement256, toString, toTwosComplement256, unsafeToInt)
import Network.Ethereum.Core.HexString (HexString, PadByte(..), fromByteString, mkHexString, numberOfBytes, padLeft, padRight, toByteString, unHex)
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, embed, mkAddress, unAddress)
import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, update, proxyBytesN)
import Network.Ethereum.Web3.Solidity.EncodingType (class EncodingType, isDynamic)
Expand All @@ -38,7 +37,7 @@ 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)
import Parsing.Combinators (lookAhead)
import Partial.Unsafe (unsafePartial)
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 Down Expand Up @@ -220,8 +219,10 @@ bytesBuilder = padRight Zero <<< fromByteString
int256HexBuilder :: BigNumber -> HexString
int256HexBuilder x =
let
a = toTwosComplement256 x
x' = unsafePartial $ fromJust $ mkHexString (toString a)
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'
Expand All @@ -236,7 +237,7 @@ int256HexParser :: forall m. Monad m => ParserT HexString m BigNumber
int256HexParser = do
bs <- unHex <$> parseBytes 32
a <- maybe (fail $ "Failed to parse bytes as BigNumber " <> bs) pure (fromString bs)
pure $ fromTwosComplement256 a
pure $ fromTwosComplement 256 a

-- | Parse an unsigned `BigNumber`
uInt256HexParser :: forall m. Monad m => ParserT HexString m BigNumber
Expand All @@ -255,22 +256,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)

mkHex s = maybe (fail $ "Unable to parse bytes from hex: " <> s) pure $ mkHexString s
{ after, before } = splitAtByteOffset n input

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

_after <- mkHex after
_before <- mkHex before
let newState = ParseState _after position' true
stateParserT $ const (Tuple _before newState)
let newState = ParseState after position' true
stateParserT $ const (Tuple before newState)
14 changes: 8 additions & 6 deletions src/Network/Ethereum/Web3/Solidity/Int.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,11 @@ module Network.Ethereum.Web3.Solidity.Int

import Prelude

import Control.Alternative ((<|>))
import Control.Monad.Gen as Gen
import Data.Maybe (Maybe(..), fromJust)
import Data.NonEmpty (NonEmpty(..))
import Network.Ethereum.Core.BigNumber (BigNumber, embed, fromString, pow)
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)
Expand All @@ -29,11 +30,12 @@ derive newtype instance ordIntN :: Ord (IntN n)

instance KnownSize n => Arbitrary (IntN n) where
arbitrary = do
sign <- embed <$> Gen.elements (NonEmpty (-1) [ 1 ])
nBytes <- (flip div 8) <$> Gen.chooseInt 1 (sizeVal (Proxy @n))
ma <- fromString <<< unHex <$> genBytes nBytes
let a = unsafePartial $ fromJust ma
pure <<< IntN $ sign * a
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

-- | Access the raw underlying integer
unIntN :: forall n. IntN n -> BigNumber
Expand Down
7 changes: 5 additions & 2 deletions src/Network/Ethereum/Web3/Solidity/UInt.purs
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,11 @@ derive newtype instance ordUIntN :: Ord (UIntN n)
instance KnownSize n => Arbitrary (UIntN n) where
arbitrary = do
nBytes <- (flip div 8) <$> Gen.chooseInt 1 (sizeVal (Proxy @n))
ma <- fromString <<< unHex <$> genBytes nBytes
let a = unsafePartial $ fromJust ma
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

-- | Access the raw underlying unsigned integer
Expand Down
2 changes: 2 additions & 0 deletions test.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -12,5 +12,7 @@ in conf
, "avar"
, "console"
, "identity"
, "enums"
, "integers"
]
}
Loading

0 comments on commit 55fc8f0

Please sign in to comment.