Skip to content

Commit

Permalink
use reifyType to cover literally every possible case
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Sep 14, 2023
1 parent 6259ab3 commit c2c47bf
Show file tree
Hide file tree
Showing 11 changed files with 384 additions and 575 deletions.
6 changes: 1 addition & 5 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 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
28 changes: 14 additions & 14 deletions src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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(..))
Expand All @@ -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)
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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

Expand Down
25 changes: 13 additions & 12 deletions src/Network/Ethereum/Web3/Solidity/Bytes.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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(..))

--------------------------------------------------------------------------------
Expand All @@ -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
21 changes: 11 additions & 10 deletions src/Network/Ethereum/Web3/Solidity/EncodingType.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand All @@ -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
Expand Down
32 changes: 15 additions & 17 deletions src/Network/Ethereum/Web3/Solidity/Int.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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(..))

--------------------------------------------------------------------------------
Expand All @@ -28,30 +26,30 @@ 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
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
Loading

0 comments on commit c2c47bf

Please sign in to comment.