Skip to content

Commit

Permalink
Experiemental (#172)
Browse files Browse the repository at this point in the history
* generator works and tests pass

* seems to work

* dep

* t clean up

* add dep

* fix instance chain

* tidy

* remove extra type param

* add one more layer of nesting for nested tuples test

* wip

* wip

* now with more nesting

* compiling sigs

* seems to work with web3-tests

* oops

* wip

* added a shitload of traces

* eureka

* remove unused internal module, simplify to/from record fields names and class def

* cleanup unused things and rename for sanity

* add vector instance

* update arrayparser logic

* fix generic impl

* update generics
  • Loading branch information
martyall authored Oct 6, 2023
1 parent 961f494 commit c369816
Show file tree
Hide file tree
Showing 19 changed files with 776 additions and 812 deletions.
2 changes: 2 additions & 0 deletions spago.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,9 @@
, "tuples"
, "typelevel-prelude"
, "unfoldable"
, "unsafe-coerce"
, "variant"
, "identity"
]
, 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
, fromData
, abiDecode
, intNFromBigNumber
, nilVector
, toVector
Expand Down
47 changes: 21 additions & 26 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, Constructor)
import Data.Lens ((.~), (%~), (?~))
import Data.Maybe (Maybe(..))
import Data.Symbol (class IsSymbol, reflectSymbol)
Expand All @@ -25,7 +24,8 @@ 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 DecodeEvent, class GenericABIDecode, class GenericABIEncode, class RecordFieldsIso, genericABIEncode, genericFromData, genericFromRecordFields)
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 Type.Proxy (Proxy(..))

Expand Down Expand Up @@ -82,38 +82,35 @@ class CallMethod (selector :: Symbol) a b where
-> Web3 (Either CallError b)

-- ^ `Web3` wrapped result
instance (Generic a rep, GenericABIEncode rep) => TxMethod s a where
instance ABIEncode a => TxMethod s a where
sendTx = _sendTransaction

instance (Generic a arep, GenericABIEncode arep, Generic b brep, GenericABIDecode brep) => 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
=> Generic a rep
=> GenericABIEncode rep
=> ABIEncode a
=> TokenUnit (Value (u ETHER))
=> TransactionOptions u
-> Tagged selector a
-> Web3 HexString
_sendTransaction txOptions dat = do
let
sel = toSelector <<< reflectSymbol $ (Proxy :: Proxy selector)
eth_sendTransaction $ txdata $ sel <> (genericABIEncode <<< untagged $ dat)
eth_sendTransaction $ txdata $ sel <> (abiEncode <<< untagged $ dat)
where
txdata d =
txOptions # _data .~ Just d
# _value
%~ map convert

_call
:: forall a arep b brep selector
:: forall a b selector
. IsSymbol selector
=> Generic a arep
=> GenericABIEncode arep
=> Generic b brep
=> GenericABIDecode brep
=> ABIEncode a
=> ABIDecode b
=> TransactionOptions NoPay
-> ChainCursor
-> Tagged selector a
Expand All @@ -124,9 +121,9 @@ _call txOptions cursor dat = do

sel = toSelector sig

fullData = sel <> (genericABIEncode <<< untagged $ dat)
res <- eth_call (txdata $ sel <> (genericABIEncode <<< untagged $ dat)) cursor
case genericFromData res of
fullData = sel <> (abiEncode <<< untagged $ dat)
res <- eth_call (txdata $ sel <> (abiEncode <<< untagged $ dat)) cursor
case abiDecode res of
Left err ->
if res == mempty then
pure <<< Left
Expand All @@ -141,28 +138,26 @@ _call txOptions cursor dat = do
txdata d = txOptions # _data .~ Just d

deployContract
:: forall a rep t
. Generic a rep
=> GenericABIEncode rep
:: forall a t
. ABIEncode a
=> TransactionOptions NoPay
-> HexString
-> Tagged t a
-> Web3 HexString
deployContract txOptions deployByteCode args =
let
txdata =
txOptions # _data ?~ deployByteCode <> genericABIEncode (untagged args)
txOptions # _data ?~ deployByteCode <> abiEncode (untagged args)
# _value
%~ map convert
in
eth_sendTransaction txdata

mkDataField
:: forall selector a name args fields l
:: forall selector a fields
. IsSymbol selector
=> Generic a (Constructor name args)
=> RecordFieldsIso args fields l
=> GenericABIEncode (Constructor name args)
=> RecordFieldsIso a () fields
=> ABIEncode a
=> Proxy (Tagged selector a)
-> Record fields
-> HexString
Expand All @@ -172,6 +167,6 @@ mkDataField _ r =

sel = toSelector sig

args = genericFromRecordFields r :: a
args = fromRecord r :: a
in
sel <> (genericABIEncode args)
sel <> abiEncode args
23 changes: 14 additions & 9 deletions src/Network/Ethereum/Web3/Contract/Events.purs
Original file line number Diff line number Diff line change
Expand Up @@ -20,21 +20,22 @@ module Network.Ethereum.Web3.Contract.Events
) where

import Prelude

import Control.Coroutine (Process, Consumer, producer, consumer, pullFrom, runProcess)
import Control.Coroutine.Transducer (Transducer, awaitForever, fromProducer, toProducer, yieldT, (=>=))
import Control.Monad.Fork.Class (bracket)
import Control.Monad.Reader.Trans (ReaderT, runReaderT)
import Control.Monad.Rec.Class (class MonadRec)
import Control.Monad.Trans.Class (lift)
import Control.Parallel (class Parallel)
import Data.Array (catMaybes, sort)
import Data.Array (sort)
import Data.Either (Either(..))
import Data.Functor.Tagged (Tagged, tagged, untagged)
import Data.Lens ((.~), (^.))
import Data.Maybe (Maybe(..))
import Data.Newtype (over)
import Data.Symbol (class IsSymbol)
import Data.Traversable (for_)
import Data.Traversable (for_, traverse)
import Data.Tuple (Tuple(..), fst)
import Data.Variant (Variant, class VariantMatchCases, expand, inj, match)
import Effect.Aff (delay, Milliseconds(..))
Expand All @@ -45,7 +46,7 @@ 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)
import Network.Ethereum.Web3.Types (BlockNumber(..), ChainCursor(..), Change(..), EventAction(..), Filter, FilterId, Web3, _fromBlock, _toBlock)
import Network.Ethereum.Web3.Types (BlockNumber(..), ChainCursor(..), Change(..), EventAction(..), Filter, FilterId, Web3, Web3Error, _fromBlock, _toBlock, throwWeb3)
import Prim.RowList as RowList
import Record as Record
import Type.Proxy (Proxy(..))
Expand Down Expand Up @@ -365,8 +366,8 @@ mkFilterChanges
=> Proxy sym
-> Proxy e
-> Array Change
-> Array (FilterChange (Variant r))
mkFilterChanges sp _ cs = catMaybes $ map pairChange cs
-> Either Web3Error (Array (FilterChange (Variant r)))
mkFilterChanges sp _ cs = traverse pairChange cs
where
pairChange rawChange = do
a :: e <- decodeEvent rawChange
Expand All @@ -387,8 +388,10 @@ instance queryAllLogs ::
) =>
FoldingWithIndex QueryAllLogs (Proxy sym) (Web3 (Array (FilterChange (Variant r')))) (Filter e) (Web3 (Array (FilterChange (Variant r)))) where
foldingWithIndex QueryAllLogs (prop :: Proxy sym) acc filter = do
changes :: Array (FilterChange (Variant r)) <- mkFilterChanges prop (Proxy :: Proxy e) <$> eth_getLogs (filter :: Filter e)
(<>) changes <$> (map (map expand) <$> acc)
eRes <- mkFilterChanges prop (Proxy :: Proxy e) <$> eth_getLogs (filter :: Filter e)
case eRes of
Left err -> throwWeb3 err
Right changes -> (<>) changes <$> (map (map expand) <$> acc)

data MultiFilterStreamState fs = MultiFilterStreamState
{ currentBlock :: BlockNumber
Expand Down Expand Up @@ -428,8 +431,10 @@ instance checkMultiFilterLogs ::
) =>
FoldingWithIndex CheckMultiFilter (Proxy sym) (Web3 (Array (FilterChange (Variant r')))) (Tagged e FilterId) (Web3 (Array (FilterChange (Variant r)))) where
foldingWithIndex CheckMultiFilter (prop :: Proxy sym) acc filterId = do
changes :: Array (FilterChange (Variant r)) <- mkFilterChanges prop (Proxy :: Proxy e) <$> eth_getFilterChanges (untagged filterId)
(<>) changes <$> (map (map expand) <$> acc)
eRes <- mkFilterChanges prop (Proxy :: Proxy e) <$> eth_getFilterChanges (untagged filterId)
case eRes of
Left err -> throwWeb3 err
Right changes -> (<>) changes <$> (map (map expand) <$> acc)

data CloseMultiFilter = CloseMultiFilter

Expand Down
33 changes: 0 additions & 33 deletions src/Network/Ethereum/Web3/Contract/Internal.purs

This file was deleted.

67 changes: 8 additions & 59 deletions src/Network/Ethereum/Web3/Solidity.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module Network.Ethereum.Web3.Solidity
( module Network.Ethereum.Web3.Solidity.Vector
, module Network.Ethereum.Web3.Solidity.Bytes
, module Network.Ethereum.Web3.Solidity.Tuple
, module Network.Ethereum.Web3.Solidity.Generic
, module Network.Ethereum.Web3.Solidity.Internal
, module Network.Ethereum.Web3.Solidity.Int
, module Network.Ethereum.Web3.Solidity.UInt
, module Network.Ethereum.Web3.Solidity.AbiEncoding
Expand All @@ -11,64 +11,13 @@ module Network.Ethereum.Web3.Solidity
, module Data.ByteString
) where

import Network.Ethereum.Web3.Solidity.Vector (Vector, unVector, nilVector, vCons, (:<), vectorLength, toVector)
import Data.ByteString (ByteString)
import Network.Ethereum.Types (BigNumber, Address)
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.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.Int (IntN, unIntN, intNFromBigNumber)
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 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.AbiEncoding (class ABIEncode, class ABIDecode, toDataBuilder, fromDataParser, fromData)
import Network.Ethereum.Web3.Solidity.Generic (class GenericABIEncode, class GenericABIDecode, class ArgsToRowListProxy, genericABIEncode, genericABIDecode, genericFromData, class RecordFieldsIso, toRecordFields, fromRecordFields, genericToRecordFields, genericFromRecordFields)
import Network.Ethereum.Types (BigNumber, Address)
import Data.ByteString (ByteString)
import Network.Ethereum.Web3.Solidity.Vector (Vector, unVector, nilVector, vCons, (:<), vectorLength, toVector)
Loading

0 comments on commit c369816

Please sign in to comment.