{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Network.Ethereum.Transaction where
import Data.ByteArray (ByteArray, convert)
import Data.ByteString (ByteString, empty)
import Data.Maybe (fromJust, fromMaybe)
import Data.RLP (packRLP, rlpEncode)
import Data.Word (Word8)
import Data.ByteArray.HexString (toBytes)
import Data.Solidity.Prim.Address (toHexString)
import Network.Ethereum.Api.Types (Call (..), Quantity (unQuantity))
import Network.Ethereum.Unit (Shannon, toWei)
encodeTransaction :: ByteArray ba
=> Call
-> Integer
-> Maybe (Integer, Integer, Word8)
-> ba
encodeTransaction Call{..} chain_id rsv =
let (to :: ByteString) = maybe mempty (toBytes . toHexString) callTo
(value :: Integer) = unQuantity $ fromJust callValue
(nonce :: Integer) = unQuantity $ fromJust callNonce
(gasPrice :: Integer) = maybe defaultGasPrice unQuantity callGasPrice
(gasLimit :: Integer) = unQuantity $ fromJust callGas
(input :: ByteString) = convert $ fromMaybe mempty callData
in convert . packRLP $ case rsv of
Nothing -> rlpEncode (nonce, gasPrice, gasLimit, to, value, input, chain_id, empty, empty)
Just (r, s, v) ->
let v' = fromIntegral v + 8 + 2 * chain_id
in rlpEncode (nonce, gasPrice, gasLimit, to, value, input, v', r, s)
where
defaultGasPrice = toWei (10 :: Shannon)