Skip to content

Commit

Permalink
test coverage
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Sep 14, 2023
1 parent 7c5f4c6 commit 5878801
Show file tree
Hide file tree
Showing 7 changed files with 36 additions and 32 deletions.
2 changes: 0 additions & 2 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@
, "control"
, "coroutine-transducers"
, "coroutines"
, "debug"
, "effect"
, "either"
, "errors"
Expand All @@ -28,7 +27,6 @@
, "partial"
, "prelude"
, "profunctor-lenses"
, "quickcheck"
, "record"
, "ring-modules"
, "simple-json"
Expand Down
6 changes: 3 additions & 3 deletions src/Network/Ethereum/Web3/Solidity/Bytes.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ 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.Core.HexString as Hex
import Network.Ethereum.Types (mkHexString)
import Partial.Unsafe (unsafePartial)
import Type.Proxy (Proxy(..))
Expand All @@ -32,8 +32,8 @@ instance showBytesN :: Show (BytesN n) where

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
bs <- Hex.generator (reflectType p)
pure $ BytesN $ Hex.toByteString bs

-- | Access the underlying raw bytestring
unBytesN :: forall n. BytesN n -> ByteString
Expand Down
6 changes: 3 additions & 3 deletions src/Network/Ethereum/Web3/Solidity/Int.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Control.Monad.Gen (class MonadGen)
import Data.Maybe (Maybe(..), fromJust)
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.Core.HexString as Hex
import Partial.Unsafe (unsafePartial)
import Type.Proxy (Proxy(..))

Expand All @@ -28,11 +28,11 @@ derive newtype instance ordIntN :: Ord (IntN n)

generator :: forall n m. Reflectable n Int => MonadGen m => Proxy n -> m (IntN n)
generator p = do
bs <- genBytes (reflectType p `div` 8)
bs <- Hex.generator (reflectType p `div` 8)
let
a =
if bs == mempty then zero
else unsafePartial $ fromJust $ fromString $ unHex $ bs
else unsafePartial $ fromJust $ fromString $ Hex.unHex $ bs
pure $ IntN $ fromTwosComplement (reflectType (Proxy @n)) a

-- | Access the raw underlying integer
Expand Down
10 changes: 5 additions & 5 deletions src/Network/Ethereum/Web3/Solidity/UInt.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ 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.Core.HexString as Hex
import Partial.Unsafe (unsafePartial)
import Test.QuickCheck (class Arbitrary)
import Test.QuickCheck.Gen as Gen
Expand All @@ -36,21 +36,21 @@ generator
-> m (UIntN n)
generator p = do
nBytes <- (flip div 8) <$> chooseInt 1 (reflectType p)
bs <- genBytes nBytes
bs <- Hex.generator nBytes
let
a =
if bs == mempty then zero
else unsafePartial $ fromJust $ fromString $ unHex bs
else unsafePartial $ fromJust $ fromString $ Hex.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 (reflectType (Proxy @n))
bs <- genBytes nBytes
bs <- Hex.generator nBytes
let
a =
if bs == mempty then zero
else unsafePartial $ fromJust $ fromString $ unHex bs
else unsafePartial $ fromJust $ fromString $ Hex.unHex bs
pure $ UIntN $ if a < zero then -a else a

-- | Access the raw underlying unsigned integer
Expand Down
1 change: 1 addition & 0 deletions test.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -14,5 +14,6 @@ in conf
, "identity"
, "enums"
, "integers"
, "quickcheck"
]
}
33 changes: 18 additions & 15 deletions test/web3/Web3Spec/Encoding/ContainersSpec.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,15 +17,15 @@ import Data.Reflectable (reifyType)
import Data.String (CodePoint, fromCodePointArray)
import Data.Tuple (Tuple(..))
import Effect.Class (liftEffect)
import Network.Ethereum.Core.HexString (genBytes, toByteString)
import Network.Ethereum.Core.HexString as Hex
import Network.Ethereum.Core.Signatures as Address
import Network.Ethereum.Web3.Solidity (class GenericABIDecode, class GenericABIEncode, Tuple4(..), Tuple5(..), genericABIEncode, genericFromData)
import Network.Ethereum.Web3.Solidity.AbiEncoding (class ABIEncode, class ABIDecode, toDataBuilder, fromData)
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, quickCheckGen, (===))
Expand All @@ -48,17 +48,18 @@ typePropertyTests =
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
quickCheckGen $ do
n <- chooseInt 1 100
x <- Hex.toByteString <$> Hex.generator n
pure $ encodeDecode x === Right x

it "can encode/decode bool" $ liftEffect $ do
quickCheck \(x :: Boolean) -> encodeDecode x === Right x

it "can encode/decode address" $ liftEffect $ do
quickCheck \(x :: Address) -> encodeDecode x === Right x
quickCheckGen $ do
x <- Address.generator
pure $ encodeDecode x === Right x

it "can encode/decode intN" $ liftEffect $ do
for_ intSizes $ \n -> quickCheckGen $ do
Expand Down Expand Up @@ -105,7 +106,9 @@ arrayTypePropertyTests = do
pure $ encodeDecode x === Right x

it "Can encode/decode address[]" $ liftEffect do
quickCheck $ \(x :: Address) -> encodeDecode x === Right x
quickCheckGen $ do
x <- Address.generator
pure $ encodeDecode x === Right x

it "Can encode/decode string[]" $ liftEffect do
quickCheck $ \(x :: Array BMPString) ->
Expand Down Expand Up @@ -147,7 +150,7 @@ vecTypePropertyTests = do
quickCheckGen $ do
k <- chooseInt 1 10
reifyType k \pk -> do
x <- Vector.generator pk (arbitrary :: Gen Address)
x <- Vector.generator pk Address.generator
pure $ encodeDecode x === Right x

it "Can encode/decode string[k]" $ liftEffect do
Expand Down Expand Up @@ -243,7 +246,7 @@ tupleTests = do
reifyType m \pm ->
reifyType k \pk -> do
int <- IntN.generator pn
addr <- arbitrary :: Gen Address
addr <- Address.generator
bool <- arbitrary :: Gen Boolean
uint <- UIntN.generator pm
bytes <- BytesN.generator pk
Expand All @@ -260,7 +263,7 @@ tupleTests = do
reifyType k2 \pk2 ->
reifyType n \pn -> do
reifyType m \pm -> do
addrs <- arrayOf (Vector.generator pk1 (arbitrary @Address))
addrs <- arrayOf (Vector.generator pk1 Address.generator)
bool <- arbitrary @Boolean
ints <- Vector.generator pk2 (IntN.generator pn)
uint <- (UIntN.generator pm)
Expand All @@ -278,8 +281,8 @@ tupleTests = do
reifyType m \pm ->
reifyType k \pk -> do
ints <- arrayOf (IntN.generator pn)
bytes <- toByteString <$> (chooseInt 1 100 >>= genBytes)
addrs <- Vector.generator pm (arrayOf $ arbitrary @Address)
bytes <- Hex.toByteString <$> (chooseInt 1 100 >>= Hex.generator)
addrs <- Vector.generator pm (arrayOf Address.generator)
strings <- arrayOf (Vector.generator pk (arbitrary @BMPString))
bool <- arbitrary :: Gen Boolean
let x = Tuple5 ints bytes addrs strings bool
Expand All @@ -295,7 +298,7 @@ tupleTests = do
reifyType k2 \pk2 ->
reifyType n \pn -> do
reifyType m \pm -> do
addrs <- arrayOf (Vector.generator pk1 (arbitrary @Address))
addrs <- arrayOf (Vector.generator pk1 Address.generator)
bool <- arbitrary @Boolean
ints <- Vector.generator pk2 (IntN.generator pn)
uint <- (UIntN.generator pm)
Expand Down
10 changes: 6 additions & 4 deletions test/web3/Web3Spec/Encoding/DataSpec.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,28 +5,30 @@ import Prelude
import Data.Functor.Tagged (Tagged, tagged)
import Effect.Class (liftEffect)
import Network.Ethereum.Core.Keccak256 (toSelector)
import Network.Ethereum.Core.Signatures as Address
import Network.Ethereum.Web3.Contract (sendTx, mkDataField)
import Network.Ethereum.Web3.Solidity (Tuple2, UIntN)
import Network.Ethereum.Web3.Solidity.AbiEncoding (toDataBuilder)
import Network.Ethereum.Web3.Solidity.Generic (genericFromRecordFields)
import Network.Ethereum.Web3.Solidity.UInt as UIntN
import Network.Ethereum.Web3.Types (Address, HexString, NoPay, TransactionOptions, Web3)
import Test.QuickCheck (quickCheck, (===))
import Test.QuickCheck (quickCheckGen, (===))
import Test.Spec (Spec, describe, it)
import Type.Proxy (Proxy(..))

spec :: Spec Unit
spec =
describe "data maker" do
it "can make the approval data" $ liftEffect do
quickCheck $ \(args :: { _spender :: Address, _value :: UIntN 256 }) ->
quickCheckGen do
args <- { _spender: _, _value: _ } <$> Address.generator <*> UIntN.generator (Proxy @256)
let
approvalD = mkDataField (Proxy :: Proxy ApproveFn) args

sel = toSelector "approve(address,uint256)"

fullDat = sel <> toDataBuilder args._spender <> toDataBuilder args._value
in
approvalD === fullDat
pure $ approvalD === fullDat

type ApproveFn = Tagged "approve(address,uint256)" (Tuple2 (Tagged "_spender" Address) (Tagged "_value" (UIntN 256)))

Expand Down

0 comments on commit 5878801

Please sign in to comment.