{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
module Network.Ethereum.Account.Internal where
import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.State.Strict (MonadState (..), StateT (..),
withStateT)
import Control.Monad.Trans (MonadTrans (..))
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
import Lens.Micro (Lens', lens)
import Data.ByteArray.HexString (HexString)
import Data.Solidity.Prim (Address)
import Network.Ethereum.Account.Class (Account)
import qualified Network.Ethereum.Api.Eth as Eth (getTransactionReceipt)
import Network.Ethereum.Api.Types (Call (..),
DefaultBlock (Latest),
TxReceipt (receiptTransactionHash))
import Network.Ethereum.Unit (Unit (..))
import Network.JsonRpc.TinyClient (JsonRpc)
data CallParam p = CallParam
{ _to :: Maybe Address
, _value :: Integer
, _gasLimit :: Maybe Integer
, _gasPrice :: Maybe Integer
, _block :: DefaultBlock
, _account :: p
} deriving Eq
to :: Lens' (CallParam p) Address
to = lens (fromMaybe def . _to) $ \a b -> a { _to = Just b }
value :: Unit value => Lens' (CallParam p) value
value = lens (fromWei . _value) $ \a b -> a { _value = toWei b }
gasLimit :: Lens' (CallParam p) Integer
gasLimit = lens (fromMaybe def . _gasLimit) $ \a b -> a { _gasLimit = Just b }
gasPrice :: Unit gasprice => Lens' (CallParam p) gasprice
gasPrice = lens (fromWei . fromMaybe def . _gasPrice) $ \a b -> a { _gasPrice = Just (toWei b) }
block :: Lens' (CallParam p) DefaultBlock
block = lens _block $ \a b -> a { _block = b }
account :: Lens' (CallParam p) p
account = lens _account $ \a b -> a { _account = b }
newtype AccountT p m a = AccountT
{ runAccountT :: StateT (CallParam p) m a }
deriving (Functor, Applicative, Monad, MonadTrans)
instance Monad m => MonadState (CallParam p) (AccountT p m) where
get = AccountT get
put = AccountT . put
withParam :: Account p (AccountT p)
=> (CallParam p -> CallParam p)
-> AccountT p m a
-> AccountT p m a
{-# INLINE withParam #-}
withParam f m = AccountT $ withStateT f $ runAccountT m
defaultCallParam :: a -> CallParam a
{-# INLINE defaultCallParam #-}
defaultCallParam = CallParam def 0 Nothing Nothing Latest
getCall :: MonadState (CallParam p) m => m Call
getCall = do
CallParam{..} <- get
return $ def { callTo = _to
, callValue = Just $ fromInteger _value
, callGas = fromInteger <$> _gasLimit
, callGasPrice = fromInteger <$> _gasPrice
}
getReceipt :: JsonRpc m => HexString -> m TxReceipt
getReceipt tx = do
mbreceipt <- Eth.getTransactionReceipt tx
case mbreceipt of
Just receipt -> return receipt
Nothing -> do
liftIO $ threadDelay 100000
getReceipt tx
updateReceipt :: JsonRpc m => TxReceipt -> m TxReceipt
{-# INLINE updateReceipt #-}
updateReceipt = getReceipt . receiptTransactionHash