Skip to content

Commit

Permalink
cleanup unused things and rename for sanity
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Oct 5, 2023
1 parent 45debae commit ffd1a51
Show file tree
Hide file tree
Showing 11 changed files with 115 additions and 141 deletions.
1 change: 0 additions & 1 deletion spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@
, "unsafe-coerce"
, "variant"
, "identity"
, "debug"
]
, packages = ./packages.dhall
, sources = [ "src/**/*.purs" ]
Expand Down
2 changes: 1 addition & 1 deletion src/Network/Ethereum/Web3.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import Network.Ethereum.Web3.Solidity
, UIntN
, Vector
, fromByteString
, parseABIValue
, abiDecode
, intNFromBigNumber
, nilVector
, toVector
Expand Down
28 changes: 12 additions & 16 deletions src/Network/Ethereum/Web3/Contract.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import Control.Monad.Error.Class (throwError)
import Data.Bifunctor (lmap)
import Data.Either (Either(..))
import Data.Functor.Tagged (Tagged, untagged)
import Data.Generic.Rep (class Generic)
import Data.Lens ((.~), (%~), (?~))
import Data.Maybe (Maybe(..))
import Data.Symbol (class IsSymbol, reflectSymbol)
Expand All @@ -25,10 +24,9 @@ import Network.Ethereum.Core.Keccak256 (toSelector)
import Network.Ethereum.Types (Address, HexString)
import Network.Ethereum.Web3.Api (eth_call, eth_sendTransaction)
import Network.Ethereum.Web3.Contract.Events (MultiFilterStreamState(..), event', FilterStreamState, ChangeReceipt, EventHandler)
import Network.Ethereum.Web3.Solidity (class ABIDecodableValue, class ABIEncodableValue, class DecodeEvent, class GRecordFieldsIso, class GenericABIDecode, class GenericABIEncode, class RecordFieldsIso, fromRecord)
import Network.Ethereum.Web3.Solidity (class ABIDecode, class ABIEncode, class DecodeEvent, class RecordFieldsIso, fromRecord)
import Network.Ethereum.Web3.Solidity.AbiEncoding (abiDecode, abiEncode)
import Network.Ethereum.Web3.Types (class TokenUnit, CallError(..), ChainCursor, ETHER, Filter, NoPay, TransactionOptions, Value, Web3, _data, _value, convert)
import Parsing (ParseError)
import Type.Proxy (Proxy(..))

class EventFilter :: forall k. k -> Constraint
Expand Down Expand Up @@ -84,16 +82,16 @@ class CallMethod (selector :: Symbol) a b where
-> Web3 (Either CallError b)

-- ^ `Web3` wrapped result
instance ABIEncodableValue a => TxMethod s a where
instance ABIEncode a => TxMethod s a where
sendTx = _sendTransaction

instance (ABIEncodableValue a, ABIDecodableValue b) => CallMethod s a b where
instance (ABIEncode a, ABIDecode b) => CallMethod s a b where
call = _call

_sendTransaction
:: forall a u rep selector
:: forall a u selector
. IsSymbol selector
=> ABIEncodableValue a
=> ABIEncode a
=> TokenUnit (Value (u ETHER))
=> TransactionOptions u
-> Tagged selector a
Expand All @@ -109,10 +107,10 @@ _sendTransaction txOptions dat = do
%~ map convert

_call
:: forall a arep b brep selector
:: forall a b selector
. IsSymbol selector
=> ABIEncodableValue a
=> ABIDecodableValue b
=> ABIEncode a
=> ABIDecode b
=> TransactionOptions NoPay
-> ChainCursor
-> Tagged selector a
Expand Down Expand Up @@ -140,8 +138,8 @@ _call txOptions cursor dat = do
txdata d = txOptions # _data .~ Just d

deployContract
:: forall a rep t
. ABIEncodableValue a
:: forall a t
. ABIEncode a
=> TransactionOptions NoPay
-> HexString
-> Tagged t a
Expand All @@ -156,12 +154,10 @@ deployContract txOptions deployByteCode args =
eth_sendTransaction txdata

mkDataField
:: forall selector a rep fields
:: forall selector a fields
. IsSymbol selector
=> RecordFieldsIso a () fields
=> ABIEncodableValue a
=> Show a
=> Show (Record fields)
=> ABIEncode a
=> Proxy (Tagged selector a)
-> Record fields
-> HexString
Expand Down
4 changes: 2 additions & 2 deletions src/Network/Ethereum/Web3/Solidity.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,11 @@ module Network.Ethereum.Web3.Solidity

import Data.ByteString (ByteString)
import Network.Ethereum.Types (BigNumber, Address)
import Network.Ethereum.Web3.Solidity.AbiEncoding (class ABIDecodableValue, class ABIEncodableValue, class EncodingType, class GEncodingType, class GenericABIDecode, class GenericABIEncode, abiValueParser, abiEncode, gIsDynamic, isDynamic, parseABIValue)
import Network.Ethereum.Web3.Solidity.AbiEncoding (class ABIDecode, class ABIEncode, class EncodingType, abiDecode, isDynamic, abiEncode)
import Network.Ethereum.Web3.Solidity.Bytes (BytesN, unBytesN, proxyBytesN, update, fromByteString)
import Network.Ethereum.Web3.Solidity.Event (class DecodeEvent, decodeEvent, class IndexedEvent, isAnonymous)
import Network.Ethereum.Web3.Solidity.Int (IntN, unIntN, intNFromBigNumber)
import Network.Ethereum.Web3.Solidity.Internal (class GRecordFieldsIso, class RecordFieldsIso, fromRecord, toRecord, fromRecord, _toRecord)
import Network.Ethereum.Web3.Solidity.Internal (class RecordFieldsIso, fromRecord, toRecord)
import Network.Ethereum.Web3.Solidity.Tuple (Tuple0(..), Tuple1(..), unTuple1, uncurry1, curry1, Tuple2(..), uncurry2, curry2, Tuple3(..), uncurry3, curry3, Tuple4(..), uncurry4, curry4, Tuple5(..), uncurry5, curry5, Tuple6(..), uncurry6, curry6, Tuple7(..), uncurry7, curry7, Tuple8(..), uncurry8, curry8, Tuple9(..), uncurry9, curry9, Tuple10(..), uncurry10, curry10, Tuple11(..), uncurry11, curry11, Tuple12(..), uncurry12, curry12, Tuple13(..), uncurry13, curry13, Tuple14(..), uncurry14, curry14, Tuple15(..), uncurry15, curry15, Tuple16(..), uncurry16, curry16)
import Network.Ethereum.Web3.Solidity.UInt (UIntN, unUIntN, uIntNFromBigNumber)
import Network.Ethereum.Web3.Solidity.Vector (Vector, unVector, nilVector, vCons, (:<), vectorLength, toVector)
136 changes: 64 additions & 72 deletions src/Network/Ethereum/Web3/Solidity/AbiEncoding.purs
Original file line number Diff line number Diff line change
@@ -1,18 +1,17 @@
module Network.Ethereum.Web3.Solidity.AbiEncoding
( class ABIDecodableValue
, abiValueParser
, class ABIEncodableValue
, abiEncode
, parseABIValue
, class GenericABIDecode
, gABIDecode
( class ABIDecode
, abiDecode
, class GenericABIEncode
, gAbiEncode
, _abiDecode
, class ABIEncode
, abiEncode
, class EncodingType
, isDynamic
, class GEncodingType
, gIsDynamic
, class GenericABIDecode
, gABIDecode
, class GenericABIEncode
, gAbiEncode
) where

import Prelude
Expand Down Expand Up @@ -91,52 +90,52 @@ else instance GEncodingType a => GEncodingType (Constructor s a) where
gIsDynamic _ = gIsDynamic (Proxy @a)

-- | Class representing values that have an encoding and decoding instance to/from a solidity type.
class EncodingType a <= ABIEncodableValue a where
class EncodingType a <= ABIEncode a where
abiEncode :: a -> HexString

instance ABIEncodableValue BigNumber where
instance ABIEncode BigNumber where
abiEncode = int256HexBuilder

else instance ABIEncodableValue Boolean where
else instance ABIEncode Boolean where
abiEncode b = uInt256HexBuilder $ if b then one else zero

else instance ABIEncodableValue Int where
else instance ABIEncode Int where
abiEncode = int256HexBuilder <<< fromInt

else instance Reflectable n Int => ABIEncodableValue (UIntN n) where
else instance Reflectable n Int => ABIEncode (UIntN n) where
abiEncode a = uInt256HexBuilder <<< unUIntN $ a

else instance ABIEncodableValue Address where
else instance ABIEncode Address where
abiEncode addr = padLeft Zero <<< unAddress $ addr

else instance Reflectable n Int => ABIEncodableValue (BytesN n) where
else instance Reflectable n Int => ABIEncode (BytesN n) where
abiEncode bs = bytesBuilder <<< unBytesN $ bs

else instance Reflectable n Int => ABIEncodableValue (IntN n) where
else instance Reflectable n Int => ABIEncode (IntN n) where
abiEncode a = int256HexBuilder <<< unIntN $ a

else instance ABIEncodableValue ByteString where
else instance ABIEncode ByteString where
abiEncode bytes = uInt256HexBuilder (fromInt $ BS.length bytes) <> bytesBuilder bytes

else instance ABIEncodableValue String where
else instance ABIEncode String where
abiEncode = abiEncode <<< BS.toUTF8

else instance ABIEncodableValue a => ABIEncodableValue (Array a) where
else instance ABIEncode a => ABIEncode (Array a) where
abiEncode l =
uInt256HexBuilder (fromInt $ length l) <>
(combineEncodedValues $ un Endo (foldMapDefaultR factorBuilder l) [])

else instance (ABIEncodableValue a, Reflectable n Int) => ABIEncodableValue (Vector n a) where
else instance (ABIEncode a, Reflectable n Int) => ABIEncode (Vector n a) where
abiEncode l =
combineEncodedValues $ un Endo (foldMapDefaultR factorBuilder $ unVector l) []

else instance ABIEncodableValue a => ABIEncodableValue (Identity a) where
else instance ABIEncode a => ABIEncode (Identity a) where
abiEncode = abiEncode <<< un Identity

else instance ABIEncodableValue a => ABIEncodableValue (Tagged s a) where
else instance ABIEncode a => ABIEncode (Tagged s a) where
abiEncode = abiEncode <<< untagged

else instance (Generic a rep, EncodingType a, GenericABIEncode rep) => ABIEncodableValue a where
else instance (Generic a rep, EncodingType a, GenericABIEncode rep) => ABIEncode a where
abiEncode a = combineEncodedValues $ un Endo (gAbiEncode $ from a) []

type EncodedValue =
Expand Down Expand Up @@ -204,13 +203,13 @@ instance GenericABIEncode NoArguments where
else instance GenericABIEncode b => GenericABIEncode (Constructor s b) where
gAbiEncode (Constructor b) = gAbiEncode b

else instance ABIEncodableValue b => GenericABIEncode (Argument b) where
else instance ABIEncode b => GenericABIEncode (Argument b) where
gAbiEncode (Argument b) = factorBuilder b

else instance (GenericABIEncode a, GenericABIEncode b) => GenericABIEncode (Product a b) where
gAbiEncode (Product a b) = gAbiEncode a <> gAbiEncode b

factorBuilder :: forall a. ABIEncodableValue a => a -> ABIDataBuilder
factorBuilder :: forall a. ABIEncode a => a -> ABIDataBuilder
factorBuilder a = Endo \encoded ->
let
encoding = abiEncode a
Expand Down Expand Up @@ -245,61 +244,61 @@ uInt256HexBuilder x =

--------------------------------------------------------------------------------

class EncodingType a <= ABIDecodableValue a where
abiValueParser :: Parser HexString a
abiDecode :: forall a. ABIDecode a => HexString -> Either ParseError a
abiDecode = flip runParser _abiDecode

parseABIValue :: forall a. ABIDecodableValue a => HexString -> Either ParseError a
parseABIValue = flip runParser abiValueParser
class EncodingType a <= ABIDecode a where
_abiDecode :: Parser HexString a

instance ABIDecodableValue BigNumber where
abiValueParser = int256HexParser
instance ABIDecode BigNumber where
_abiDecode = int256HexParser

else instance ABIDecodableValue Boolean where
abiValueParser = toBool <$> uInt256HexParser
else instance ABIDecode Boolean where
_abiDecode = toBool <$> uInt256HexParser
where
toBool bn = not $ bn == zero

else instance ABIDecodableValue Int where
abiValueParser = unsafeToInt <$> int256HexParser
else instance ABIDecode Int where
_abiDecode = unsafeToInt <$> int256HexParser

else instance ABIDecodableValue Address where
abiValueParser = do
else instance ABIDecode Address where
_abiDecode = do
_ <- parseBytes 12
maddr <- mkAddress <$> parseBytes 20
maybe (fail "Address is 20 bytes, receieved more") pure maddr

else instance ABIDecodableValue ByteString where
abiValueParser = do
len <- abiValueParser
else instance ABIDecode ByteString where
_abiDecode = do
len <- _abiDecode
toByteString <$> parseBytes len

else instance ABIDecodableValue String where
abiValueParser = BS.fromUTF8 <$> abiValueParser
else instance ABIDecode String where
_abiDecode = BS.fromUTF8 <$> _abiDecode

else instance Reflectable n Int => ABIDecodableValue (BytesN n) where
abiValueParser = do
else instance Reflectable n Int => ABIDecode (BytesN n) where
_abiDecode = do
let
len = reflectType (Proxy :: Proxy n)
zeroBytes = 32 - len
raw <- parseBytes len
_ <- parseBytes zeroBytes
pure <<< update proxyBytesN <<< toByteString $ raw

else instance (Reflectable n Int, ABIDecodableValue a) => ABIDecodableValue (Vector n a) where
abiValueParser =
else instance (Reflectable n Int, ABIDecode a) => ABIDecode (Vector n a) where
_abiDecode =
let
len = reflectType (Proxy :: Proxy n)
in
replicateA len factorParser

else instance ABIDecodableValue a => ABIDecodableValue (Array a) where
abiValueParser = do
len <- abiValueParser
else instance ABIDecode a => ABIDecode (Array a) where
_abiDecode = do
len <- _abiDecode
resetOffset
replicateA len factorParser

else instance Reflectable n Int => ABIDecodableValue (UIntN n) where
abiValueParser = do
else instance Reflectable n Int => ABIDecode (UIntN n) where
_abiDecode = do
a <- uInt256HexParser
maybe (fail $ msg a) pure <<< uIntNFromBigNumber (Proxy @n) $ a
where
Expand All @@ -309,8 +308,8 @@ else instance Reflectable n Int => ABIDecodableValue (UIntN n) where
in
"Couldn't parse as uint" <> show size <> " : " <> show n

else instance Reflectable n Int => ABIDecodableValue (IntN n) where
abiValueParser = do
else instance Reflectable n Int => ABIDecode (IntN n) where
_abiDecode = do
a <- int256HexParser
maybe (fail $ msg a) pure <<< intNFromBigNumber (Proxy :: Proxy n) $ a
where
Expand All @@ -320,29 +319,22 @@ else instance Reflectable n Int => ABIDecodableValue (IntN n) where
in
"Couldn't parse as int" <> show size <> " : " <> show n

else instance ABIDecodableValue a => ABIDecodableValue (Tagged s a) where
abiValueParser = tagged <$> abiValueParser
else instance ABIDecode a => ABIDecode (Tagged s a) where
_abiDecode = tagged <$> _abiDecode

else instance ABIDecodableValue a => ABIDecodableValue (Identity a) where
abiValueParser = Identity <$> abiValueParser
else instance ABIDecode a => ABIDecode (Identity a) where
_abiDecode = Identity <$> _abiDecode

else instance (Generic a rep, EncodingType a, GenericABIDecode rep) => ABIDecodableValue a where
abiValueParser = to <$> gABIDecode
else instance (Generic a rep, EncodingType a, GenericABIDecode rep) => ABIDecode a where
_abiDecode = to <$> gABIDecode

class GenericABIDecode a where
gABIDecode :: Parser HexString a

abiDecode
:: forall a
. ABIDecodableValue a
=> HexString
-> Either ParseError a
abiDecode hex = runParser hex abiValueParser

instance GenericABIDecode NoArguments where
gABIDecode = pure NoArguments

else instance ABIDecodableValue a => GenericABIDecode (Argument a) where
else instance ABIDecode a => GenericABIDecode (Argument a) where
gABIDecode = Argument <$> factorParser

else instance (IsSymbol name, GenericABIDecode a) => GenericABIDecode (Constructor name a) where
Expand All @@ -351,18 +343,18 @@ else instance (IsSymbol name, GenericABIDecode a) => GenericABIDecode (Construct
else instance (GenericABIDecode b, GenericABIDecode a) => GenericABIDecode (Product a b) where
gABIDecode = Product <$> gABIDecode <*> gABIDecode

factorParser :: forall a. ABIDecodableValue a => Parser HexString a
factorParser :: forall a. ABIDecode a => Parser HexString a
factorParser
| isDynamic (Proxy :: Proxy a) = do
dataOffset <- abiValueParser
dataOffset <- _abiDecode
found <- lookAhead
$ do
(ParseState _ (Position { index }) _) <- getParserT
void $ parseBytes (dataOffset - index)
resetOffset
abiValueParser
_abiDecode
pure found
| otherwise = abiValueParser
| otherwise = _abiDecode

-- | Parse as a signed `BigNumber`
int256HexParser :: forall m. Monad m => ParserT HexString m BigNumber
Expand Down
Loading

0 comments on commit ffd1a51

Please sign in to comment.