{-# LANGUAGE ScopedTypeVariables #-}
module Network.Ethereum.Contract.Method (
Method(..)
, call
, sendTx
) where
import Control.Monad.Catch (throwM)
import Data.Monoid ((<>))
import Data.Proxy (Proxy (..))
import Network.Ethereum.ABI.Class (ABIGet, ABIPut, ABIType (..))
import Network.Ethereum.ABI.Codec (decode, encode)
import Network.Ethereum.ABI.Prim.Bytes (Bytes)
import qualified Network.Ethereum.Web3.Eth as Eth
import Network.Ethereum.Web3.Provider (Web3, Web3Error (ParserFail))
import Network.Ethereum.Web3.Types (Call (callData), DefaultBlock,
TxHash)
class ABIPut a => Method a where
selector :: Proxy a -> Bytes
instance ABIType () where
isDynamic _ = False
instance ABIPut ()
instance Method () where
selector = mempty
sendTx :: Method a
=> Call
-> a
-> Web3 TxHash
sendTx call' (dat :: a) =
let sel = selector (Proxy :: Proxy a)
in Eth.sendTransaction (call' { callData = Just $ sel <> encode dat })
call :: (Method a, ABIGet b)
=> Call
-> DefaultBlock
-> a
-> Web3 b
call call' mode (dat :: a) = do
let sel = selector (Proxy :: Proxy a)
res <- Eth.call (call' { callData = Just $ sel <> encode dat }) mode
case decode res of
Left e -> throwM $ ParserFail $ "Unable to parse response: " ++ e
Right x -> return x