{-# LANGUAGE FlexibleContexts #-}
module Network.Ethereum.Account.Safe where
import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans (lift)
import Network.Ethereum.Account.Class (Account (send))
import Network.Ethereum.Account.Internal (updateReceipt)
import qualified Network.Ethereum.Api.Eth as Eth
import Network.Ethereum.Api.Types (TxReceipt (receiptBlockNumber))
import Network.Ethereum.Contract.Method (Method)
import Network.JsonRpc.TinyClient (JsonRpc)
safeSend :: (Account p t, JsonRpc m, Method args, Monad (t m))
=> Integer
-> args
-> t m TxReceipt
safeSend b a = lift . waiting =<< send a
where
waiting receipt =
case receiptBlockNumber receipt of
Nothing -> do
liftIO $ threadDelay 1000000
waiting =<< updateReceipt receipt
Just bn -> do
current <- Eth.blockNumber
if current - bn >= fromInteger b
then return receipt
else do liftIO $ threadDelay 1000000
waiting receipt
safeConfirmations :: Integer
safeConfirmations = 10