Skip to content

Commit

Permalink
rethrow web3 error (#170)
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall authored Sep 26, 2023
1 parent 2fe4e76 commit 961f494
Show file tree
Hide file tree
Showing 3 changed files with 23 additions and 28 deletions.
8 changes: 5 additions & 3 deletions src/Network/Ethereum/Web3/Contract.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,21 +11,23 @@ module Network.Ethereum.Web3.Contract
) where

import Prelude

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 Type.Proxy (Proxy(..))
import Data.Symbol (class IsSymbol, reflectSymbol)
import Effect.Exception (error)
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.Types (class TokenUnit, CallError(..), ChainCursor, ETHER, Filter, NoPay, TransactionOptions, Value, Web3, _data, _value, convert, throwWeb3)
import Network.Ethereum.Web3.Types (class TokenUnit, CallError(..), ChainCursor, ETHER, Filter, NoPay, TransactionOptions, Value, Web3, _data, _value, convert)
import Type.Proxy (Proxy(..))

class EventFilter :: forall k. k -> Constraint
class EventFilter e where
Expand Down Expand Up @@ -133,7 +135,7 @@ _call txOptions cursor dat = do
, _data: fullData
}
else
throwWeb3 <<< error $ show err
throwError $ error $ show err
Right x -> pure $ Right x
where
txdata d = txOptions # _data .~ Just d
Expand Down
24 changes: 9 additions & 15 deletions src/Network/Ethereum/Web3/JsonRPC.purs
Original file line number Diff line number Diff line change
@@ -1,19 +1,18 @@
module Network.Ethereum.Web3.JsonRPC where

import Prelude
import Effect.Aff (Aff, Error, attempt, error)
import Effect.Aff.Class (liftAff)
import Effect.Aff.Compat (fromEffectFnAff, EffectFnAff)
import Control.Monad.Error.Class (throwError)

import Control.Monad.Except (runExcept)
import Control.Monad.Reader (ask)
import Data.Array ((:))
import Data.Either (Either(..))
import Effect.Aff (Aff, attempt)
import Effect.Aff.Class (liftAff)
import Effect.Aff.Compat (fromEffectFnAff, EffectFnAff)
import Foreign (Foreign)
-- import Foreign.Generic (defaultOptions, genericEncodeJSON)
import Network.Ethereum.Web3.Types (MethodName, Request, Response(..), Web3, Web3Error(..), mkRequest)
import Network.Ethereum.Web3.Types (MethodName, Request, Response(..), Web3, Web3Error(..), mkRequest, throwWeb3)
import Network.Ethereum.Web3.Types.Provider (Provider)
import Simple.JSON (class ReadForeign, class WriteForeign, readImpl, writeImpl, writeJSON)
import Simple.JSON (class ReadForeign, class WriteForeign, readImpl, writeImpl)

--------------------------------------------------------------------------------
-- * Asynchronous RPC Calls
Expand All @@ -27,18 +26,13 @@ instance ReadForeign a => Remote (Web3 a) where
p <- ask
res' <- liftAff $ attempt $ f p mempty
case res' of
Left uncheckedErr -> throwError $ asError $ RemoteError $ show uncheckedErr
Left uncheckedErr -> throwWeb3 $ RemoteError (show uncheckedErr)
Right res -> case runExcept $ readImpl res of
-- case where we get either a known Web3Error or a foreign value
Left err -> throwError $ asError $ ParserError $ show err
Left err -> throwWeb3 $ ParserError $ show err
Right (Response r) -> case r of
Left err -> throwError $ asError err
Left err -> throwWeb3 err
Right a -> pure a
where
-- NOTE: this is a bit hacky
-- see Network.Ethereum.Web3.Types.Types#parseMsg
asError :: Web3Error -> Error
asError e = error $ writeJSON e

instance (WriteForeign a, Remote b) => Remote (a -> b) where
remote_ f x = remote_ $ \p args -> f p (writeImpl x : args)
Expand Down
19 changes: 9 additions & 10 deletions src/Network/Ethereum/Web3/Types/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ module Network.Ethereum.Web3.Types.Types
) where

import Prelude

import Control.Alt (class Alt)
import Control.Alternative (class Alternative, class Plus, (<|>))
import Control.Error.Util (hush)
Expand All @@ -54,24 +55,24 @@ import Control.Parallel.Class (class Parallel, parallel, sequential)
import Data.Argonaut as A
import Data.Either (Either(..))
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Data.Lens.Lens (Lens', Lens, lens)
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (class Newtype, unwrap)
import Data.Ordering (invert)
import Data.Show.Generic (genericShow)
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff, Fiber, ParAff, attempt, forkAff, message, throwError)
import Effect.Aff (Aff, Fiber, ParAff, attempt, error, forkAff, message, throwError)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (class MonadEffect, liftEffect)
import Effect.Exception (Error, throwException)
import Effect.Class (class MonadEffect)
import Effect.Exception (Error)
import Foreign (F, Foreign, ForeignError(..), fail, isNull, readBoolean, readString)
import Foreign.Object as FO
import Foreign.Index (readProp)
import Foreign.Object as FO
import Network.Ethereum.Types (Address, BigNumber, HexString)
import Network.Ethereum.Web3.Types.EtherUnit (ETHER, Wei)
import Network.Ethereum.Web3.Types.Provider (Provider)
import Network.Ethereum.Web3.Types.TokenUnit (class TokenUnit, MinorUnit, NoPay, Value, convert)
import Simple.JSON (class ReadForeign, class WriteForeign, readImpl, writeImpl, readJSON', undefined)
import Simple.JSON (class ReadForeign, class WriteForeign, readImpl, readJSON', undefined, writeImpl, writeJSON)

--------------------------------------------------------------------------------
-- * Block
Expand Down Expand Up @@ -381,9 +382,6 @@ instance Parallel Web3Par Web3 where
parallel (Web3 m) = Web3Par (parallel m)
sequential (Web3Par m) = Web3 (sequential m)

throwWeb3 :: forall a. Error -> Web3 a
throwWeb3 = liftEffect <<< throwException

-- | Run an asynchronous `ETH` action
runWeb3 :: forall a. Provider -> Web3 a -> Aff (Either Web3Error a)
runWeb3 p (Web3 action) =
Expand All @@ -400,7 +398,8 @@ runWeb3 p (Web3 action) =
parseMsg :: String -> Maybe Web3Error
parseMsg = hush <<< runExcept <<< readJSON'

-- parseMsg msg = hush $ runExcept $ genericDecodeJSON defaultOptions msg
throwWeb3 :: forall a. Web3Error -> Web3 a
throwWeb3 e = throwError $ error $ writeJSON e

-- | Fork an asynchronous `ETH` action
forkWeb3
Expand Down

0 comments on commit 961f494

Please sign in to comment.