module EVM.Transaction where

import Prelude hiding (Word)

import EVM (initialContract, ceilDiv)
import EVM.FeeSchedule
import EVM.RLP
import EVM.Types
import EVM.Format (hexText)
import EVM.Expr (litAddr)
import EVM.Sign

import Optics.Core hiding (cons)

import Data.ByteString (ByteString, cons)
import Data.Map (Map)
import Data.Maybe (fromMaybe, isNothing, fromJust)
import GHC.Generics (Generic)

import Data.Aeson (FromJSON (..))
import qualified Data.Aeson        as JSON
import qualified Data.Aeson.Types  as JSON
import qualified Data.ByteString   as BS
import qualified Data.Map          as Map
import Data.Word (Word64)
import Numeric (showHex)

data AccessListEntry = AccessListEntry {
  AccessListEntry -> Addr
address :: Addr,
  AccessListEntry -> [W256]
storageKeys :: [W256]
} deriving (Int -> AccessListEntry -> ShowS
[AccessListEntry] -> ShowS
AccessListEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccessListEntry] -> ShowS
$cshowList :: [AccessListEntry] -> ShowS
show :: AccessListEntry -> String
$cshow :: AccessListEntry -> String
showsPrec :: Int -> AccessListEntry -> ShowS
$cshowsPrec :: Int -> AccessListEntry -> ShowS
Show, forall x. Rep AccessListEntry x -> AccessListEntry
forall x. AccessListEntry -> Rep AccessListEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccessListEntry x -> AccessListEntry
$cfrom :: forall x. AccessListEntry -> Rep AccessListEntry x
Generic)

instance JSON.ToJSON AccessListEntry

data TxType = LegacyTransaction
            | AccessListTransaction
            | EIP1559Transaction
  deriving (Int -> TxType -> ShowS
[TxType] -> ShowS
TxType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxType] -> ShowS
$cshowList :: [TxType] -> ShowS
show :: TxType -> String
$cshow :: TxType -> String
showsPrec :: Int -> TxType -> ShowS
$cshowsPrec :: Int -> TxType -> ShowS
Show, TxType -> TxType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxType -> TxType -> Bool
$c/= :: TxType -> TxType -> Bool
== :: TxType -> TxType -> Bool
$c== :: TxType -> TxType -> Bool
Eq, forall x. Rep TxType x -> TxType
forall x. TxType -> Rep TxType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxType x -> TxType
$cfrom :: forall x. TxType -> Rep TxType x
Generic)

instance JSON.ToJSON TxType where
  toJSON :: TxType -> Value
toJSON TxType
t = case TxType
t of
               TxType
EIP1559Transaction    -> Value
"0x2" -- EIP1559
               TxType
LegacyTransaction     -> Value
"0x1" -- EIP2718
               TxType
AccessListTransaction -> Value
"0x1" -- EIP2930


data Transaction = Transaction {
    Transaction -> ByteString
txdata            :: ByteString,
    Transaction -> Word64
gasLimit          :: Word64,
    Transaction -> Maybe W256
gasPrice          :: Maybe W256,
    Transaction -> W256
nonce             :: W256,
    Transaction -> W256
r                 :: W256,
    Transaction -> W256
s                 :: W256,
    Transaction -> Maybe Addr
toAddr            :: Maybe Addr,
    Transaction -> W256
v                 :: W256,
    Transaction -> W256
value             :: W256,
    Transaction -> TxType
txtype            :: TxType,
    Transaction -> [AccessListEntry]
accessList        :: [AccessListEntry],
    Transaction -> Maybe W256
maxPriorityFeeGas :: Maybe W256,
    Transaction -> Maybe W256
maxFeePerGas      :: Maybe W256,
    Transaction -> W256
chainId           :: W256
} deriving (Int -> Transaction -> ShowS
[Transaction] -> ShowS
Transaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show, forall x. Rep Transaction x -> Transaction
forall x. Transaction -> Rep Transaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic)

instance JSON.ToJSON Transaction where
  toJSON :: Transaction -> Value
toJSON Transaction
t = [Pair] -> Value
JSON.object [ (Key
"input",             (forall a. ToJSON a => a -> Value
JSON.toJSON (ByteString -> ByteStringS
ByteStringS Transaction
t.txdata)))
                         , (Key
"gas",               (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ String
"0x" forall a. [a] -> [a] -> [a]
++ forall a. (Integral a, Show a) => a -> ShowS
showHex (forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ Transaction
t.gasLimit) String
""))
                         , (Key
"gasPrice",          (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Transaction
t.gasPrice))
                         , (Key
"v",                 (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ (Transaction
t.v)forall a. Num a => a -> a -> a
-W256
27))
                         , (Key
"r",                 (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Transaction
t.r))
                         , (Key
"s",                 (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Transaction
t.s))
                         , (Key
"to",                (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ Transaction
t.toAddr))
                         , (Key
"nonce",             (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Transaction
t.nonce))
                         , (Key
"value",             (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Transaction
t.value))
                         , (Key
"type",              (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ Transaction
t.txtype))
                         , (Key
"accessList",        (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ Transaction
t.accessList))
                         , (Key
"maxPriorityFeePerGas", (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Transaction
t.maxPriorityFeeGas))
                         , (Key
"maxFeePerGas",      (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Transaction
t.maxFeePerGas))
                         , (Key
"chainId",           (forall a. ToJSON a => a -> Value
JSON.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Transaction
t.chainId))
                         ]

emptyTransaction :: Transaction
emptyTransaction :: Transaction
emptyTransaction = Transaction { $sel:txdata:Transaction :: ByteString
txdata = forall a. Monoid a => a
mempty
                               , $sel:gasLimit:Transaction :: Word64
gasLimit = Word64
0
                               , $sel:gasPrice:Transaction :: Maybe W256
gasPrice = forall a. Maybe a
Nothing
                               , $sel:nonce:Transaction :: W256
nonce = W256
0
                               , $sel:r:Transaction :: W256
r = W256
0
                               , $sel:s:Transaction :: W256
s = W256
0
                               , $sel:toAddr:Transaction :: Maybe Addr
toAddr = forall a. Maybe a
Nothing
                               , $sel:v:Transaction :: W256
v = W256
0
                               , $sel:value:Transaction :: W256
value = W256
0
                               , $sel:txtype:Transaction :: TxType
txtype = TxType
EIP1559Transaction
                               , $sel:accessList:Transaction :: [AccessListEntry]
accessList = []
                               , $sel:maxPriorityFeeGas:Transaction :: Maybe W256
maxPriorityFeeGas = forall a. Maybe a
Nothing
                               , $sel:maxFeePerGas:Transaction :: Maybe W256
maxFeePerGas = forall a. Maybe a
Nothing
                               , $sel:chainId:Transaction :: W256
chainId = W256
1
                               }

-- | utility function for getting a more useful representation of accesslistentries
-- duplicates only matter for gas computation
txAccessMap :: Transaction -> Map Addr [W256]
txAccessMap :: Transaction -> Map Addr [W256]
txAccessMap Transaction
tx = ((forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. [a] -> [a] -> [a]
(++)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AccessListEntry] -> [(Addr, [W256])]
makeTups) Transaction
tx.accessList
  where makeTups :: [AccessListEntry] -> [(Addr, [W256])]
makeTups = forall a b. (a -> b) -> [a] -> [b]
map (\AccessListEntry
ale -> (AccessListEntry
ale.address , AccessListEntry
ale.storageKeys ))

-- Given Transaction, it recovers the address that sent it
sender :: Transaction -> Maybe Addr
sender :: Transaction -> Maybe Addr
sender Transaction
tx = W256 -> W256 -> W256 -> W256 -> Maybe Addr
ecrec W256
v' Transaction
tx.r  Transaction
tx.s W256
hash
  where hash :: W256
hash = ByteString -> W256
keccak' (Transaction -> ByteString
signingData Transaction
tx)
        v :: W256
v    = Transaction
tx.v
        v' :: W256
v'   = if W256
v forall a. Eq a => a -> a -> Bool
== W256
27 Bool -> Bool -> Bool
|| W256
v forall a. Eq a => a -> a -> Bool
== W256
28 then W256
v
               else W256
27 forall a. Num a => a -> a -> a
+ W256
v

sign :: Integer -> Transaction -> Transaction
sign :: Integer -> Transaction -> Transaction
sign Integer
sk Transaction
tx = Transaction
tx { $sel:v:Transaction :: W256
v = forall a b. (Integral a, Num b) => a -> b
num Word8
v, $sel:r:Transaction :: W256
r = W256
r, $sel:s:Transaction :: W256
s = W256
s}
  where
    hash :: W256
hash = ByteString -> W256
keccak' forall a b. (a -> b) -> a -> b
$ Transaction -> ByteString
signingData Transaction
tx
    (Word8
v, W256
r, W256
s) = W256 -> Integer -> (Word8, W256, W256)
EVM.Sign.sign W256
hash Integer
sk

signingData :: Transaction -> ByteString
signingData :: Transaction -> ByteString
signingData Transaction
tx =
  case Transaction
tx.txtype of
    TxType
LegacyTransaction -> if W256
v forall a. Eq a => a -> a -> Bool
== (Transaction
tx.chainId forall a. Num a => a -> a -> a
* W256
2 forall a. Num a => a -> a -> a
+ W256
35) Bool -> Bool -> Bool
|| W256
v forall a. Eq a => a -> a -> Bool
== (Transaction
tx.chainId forall a. Num a => a -> a -> a
* W256
2 forall a. Num a => a -> a -> a
+ W256
36)
      then ByteString
eip155Data
      else ByteString
normalData
    TxType
AccessListTransaction -> ByteString
eip2930Data
    TxType
EIP1559Transaction -> ByteString
eip1559Data
  where v :: W256
v          = forall a b. (Integral a, Num b) => a -> b
fromIntegral Transaction
tx.v
        to' :: RLP
to'        = case Transaction
tx.toAddr of
          Just Addr
a  -> ByteString -> RLP
BS forall a b. (a -> b) -> a -> b
$ Addr -> ByteString
word160Bytes Addr
a
          Maybe Addr
Nothing -> ByteString -> RLP
BS forall a. Monoid a => a
mempty
        maxFee :: W256
maxFee = forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.maxFeePerGas
        maxPrio :: W256
maxPrio = forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.maxPriorityFeeGas
        gasPrice :: W256
gasPrice = forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.gasPrice
        accessList :: [AccessListEntry]
accessList = Transaction
tx.accessList
        rlpAccessList :: RLP
rlpAccessList = [RLP] -> RLP
EVM.RLP.List forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\AccessListEntry
accessEntry ->
          [RLP] -> RLP
EVM.RLP.List [ByteString -> RLP
BS forall a b. (a -> b) -> a -> b
$ Addr -> ByteString
word160Bytes AccessListEntry
accessEntry.address,
                        [RLP] -> RLP
EVM.RLP.List forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map W256 -> RLP
rlpWordFull AccessListEntry
accessEntry.storageKeys]
          ) [AccessListEntry]
accessList
        normalData :: ByteString
normalData = [RLP] -> ByteString
rlpList [W256 -> RLP
rlpWord256 Transaction
tx.nonce,
                              W256 -> RLP
rlpWord256 W256
gasPrice,
                              W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num Transaction
tx.gasLimit),
                              RLP
to',
                              W256 -> RLP
rlpWord256 Transaction
tx.value,
                              ByteString -> RLP
BS Transaction
tx.txdata]
        eip155Data :: ByteString
eip155Data = [RLP] -> ByteString
rlpList [W256 -> RLP
rlpWord256 Transaction
tx.nonce,
                              W256 -> RLP
rlpWord256 W256
gasPrice,
                              W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num Transaction
tx.gasLimit),
                              RLP
to',
                              W256 -> RLP
rlpWord256 Transaction
tx.value,
                              ByteString -> RLP
BS Transaction
tx.txdata,
                              W256 -> RLP
rlpWord256 Transaction
tx.chainId,
                              W256 -> RLP
rlpWord256 W256
0x0,
                              W256 -> RLP
rlpWord256 W256
0x0]
        eip1559Data :: ByteString
eip1559Data = Word8 -> ByteString -> ByteString
cons Word8
0x02 forall a b. (a -> b) -> a -> b
$ [RLP] -> ByteString
rlpList [
          W256 -> RLP
rlpWord256 Transaction
tx.chainId,
          W256 -> RLP
rlpWord256 Transaction
tx.nonce,
          W256 -> RLP
rlpWord256 W256
maxPrio,
          W256 -> RLP
rlpWord256 W256
maxFee,
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num Transaction
tx.gasLimit),
          RLP
to',
          W256 -> RLP
rlpWord256 Transaction
tx.value,
          ByteString -> RLP
BS Transaction
tx.txdata,
          RLP
rlpAccessList]

        eip2930Data :: ByteString
eip2930Data = Word8 -> ByteString -> ByteString
cons Word8
0x01 forall a b. (a -> b) -> a -> b
$ [RLP] -> ByteString
rlpList [
          W256 -> RLP
rlpWord256 Transaction
tx.chainId,
          W256 -> RLP
rlpWord256 Transaction
tx.nonce,
          W256 -> RLP
rlpWord256 W256
gasPrice,
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num Transaction
tx.gasLimit),
          RLP
to',
          W256 -> RLP
rlpWord256 Transaction
tx.value,
          ByteString -> RLP
BS Transaction
tx.txdata,
          RLP
rlpAccessList]

accessListPrice :: FeeSchedule Word64 -> [AccessListEntry] -> Word64
accessListPrice :: FeeSchedule Word64 -> [AccessListEntry] -> Word64
accessListPrice FeeSchedule Word64
fs [AccessListEntry]
al =
    forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (forall a b. (a -> b) -> [a] -> [b]
map
      (\AccessListEntry
ale ->
        FeeSchedule Word64
fs.g_access_list_address  forall a. Num a => a -> a -> a
+
        (FeeSchedule Word64
fs.g_access_list_storage_key  forall a. Num a => a -> a -> a
* (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length) AccessListEntry
ale.storageKeys))
        [AccessListEntry]
al)

txGasCost :: FeeSchedule Word64 -> Transaction -> Word64
txGasCost :: FeeSchedule Word64 -> Transaction -> Word64
txGasCost FeeSchedule Word64
fs Transaction
tx =
  let calldata :: ByteString
calldata     = Transaction
tx.txdata
      zeroBytes :: Int
zeroBytes    = Word8 -> ByteString -> Int
BS.count Word8
0 ByteString
calldata
      nonZeroBytes :: Int
nonZeroBytes = ByteString -> Int
BS.length ByteString
calldata forall a. Num a => a -> a -> a
- Int
zeroBytes
      baseCost :: Word64
baseCost     = FeeSchedule Word64
fs.g_transaction
        forall a. Num a => a -> a -> a
+ (if forall a. Maybe a -> Bool
isNothing Transaction
tx.toAddr then FeeSchedule Word64
fs.g_txcreate forall a. Num a => a -> a -> a
+ Word64
initcodeCost else Word64
0)
        forall a. Num a => a -> a -> a
+ (FeeSchedule Word64 -> [AccessListEntry] -> Word64
accessListPrice FeeSchedule Word64
fs Transaction
tx.accessList )
      zeroCost :: Word64
zeroCost     = FeeSchedule Word64
fs.g_txdatazero
      nonZeroCost :: Word64
nonZeroCost  = FeeSchedule Word64
fs.g_txdatanonzero
      initcodeCost :: Word64
initcodeCost = FeeSchedule Word64
fs.g_initcodeword forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
num (forall a. (Num a, Integral a) => a -> a -> a
ceilDiv (ByteString -> Int
BS.length ByteString
calldata) Int
32)
  in Word64
baseCost forall a. Num a => a -> a -> a
+ Word64
zeroCost forall a. Num a => a -> a -> a
* (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
zeroBytes) forall a. Num a => a -> a -> a
+ Word64
nonZeroCost forall a. Num a => a -> a -> a
* (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nonZeroBytes)

instance FromJSON AccessListEntry where
  parseJSON :: Value -> Parser AccessListEntry
parseJSON (JSON.Object Object
val) = do
    Addr
accessAddress_ <- Object -> Key -> Parser Addr
addrField Object
val Key
"address"
    [W256]
accessStorageKeys_ <- (Object
val forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"storageKeys") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. FromJSON a => Value -> Parser [a]
parseJSONList
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Addr -> [W256] -> AccessListEntry
AccessListEntry Addr
accessAddress_ [W256]
accessStorageKeys_
  parseJSON Value
invalid =
    forall a. String -> Value -> Parser a
JSON.typeMismatch String
"AccessListEntry" Value
invalid

instance FromJSON Transaction where
  parseJSON :: Value -> Parser Transaction
parseJSON (JSON.Object Object
val) = do
    ByteString
tdata    <- Text -> ByteString
hexText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
val forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"data")
    Word64
gasLimit <- Object -> Key -> Parser Word64
word64Field Object
val Key
"gasLimit"
    Maybe W256
gasPrice <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Read a => String -> a
read forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"gasPrice"
    Maybe W256
maxPrio  <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Read a => String -> a
read forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"maxPriorityFeePerGas"
    Maybe W256
maxFee   <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Read a => String -> a
read forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"maxFeePerGas"
    W256
nonce    <- Object -> Key -> Parser W256
wordField Object
val Key
"nonce"
    W256
r        <- Object -> Key -> Parser W256
wordField Object
val Key
"r"
    W256
s        <- Object -> Key -> Parser W256
wordField Object
val Key
"s"
    Maybe Addr
toAddr   <- Object -> Key -> Parser (Maybe Addr)
addrFieldMaybe Object
val Key
"to"
    W256
v        <- Object -> Key -> Parser W256
wordField Object
val Key
"v"
    W256
value    <- Object -> Key -> Parser W256
wordField Object
val Key
"value"
    Maybe Int
txType   <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Read a => String -> a
read :: String -> Int) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
val forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"type")
    case Maybe Int
txType of
      Just Int
0x00 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteString
-> Word64
-> Maybe W256
-> W256
-> W256
-> W256
-> Maybe Addr
-> W256
-> W256
-> TxType
-> [AccessListEntry]
-> Maybe W256
-> Maybe W256
-> W256
-> Transaction
Transaction ByteString
tdata Word64
gasLimit Maybe W256
gasPrice W256
nonce W256
r W256
s Maybe Addr
toAddr W256
v W256
value TxType
LegacyTransaction [] forall a. Maybe a
Nothing forall a. Maybe a
Nothing W256
1
      Just Int
0x01 -> do
        [AccessListEntry]
accessListEntries <- (Object
val forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"accessList") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. FromJSON a => Value -> Parser [a]
parseJSONList
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteString
-> Word64
-> Maybe W256
-> W256
-> W256
-> W256
-> Maybe Addr
-> W256
-> W256
-> TxType
-> [AccessListEntry]
-> Maybe W256
-> Maybe W256
-> W256
-> Transaction
Transaction ByteString
tdata Word64
gasLimit Maybe W256
gasPrice W256
nonce W256
r W256
s Maybe Addr
toAddr W256
v W256
value TxType
AccessListTransaction [AccessListEntry]
accessListEntries forall a. Maybe a
Nothing forall a. Maybe a
Nothing W256
1
      Just Int
0x02 -> do
        [AccessListEntry]
accessListEntries <- (Object
val forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"accessList") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. FromJSON a => Value -> Parser [a]
parseJSONList
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteString
-> Word64
-> Maybe W256
-> W256
-> W256
-> W256
-> Maybe Addr
-> W256
-> W256
-> TxType
-> [AccessListEntry]
-> Maybe W256
-> Maybe W256
-> W256
-> Transaction
Transaction ByteString
tdata Word64
gasLimit Maybe W256
gasPrice W256
nonce W256
r W256
s Maybe Addr
toAddr W256
v W256
value TxType
EIP1559Transaction [AccessListEntry]
accessListEntries Maybe W256
maxPrio Maybe W256
maxFee W256
1
      Just Int
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unrecognized custom transaction type"
      Maybe Int
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteString
-> Word64
-> Maybe W256
-> W256
-> W256
-> W256
-> Maybe Addr
-> W256
-> W256
-> TxType
-> [AccessListEntry]
-> Maybe W256
-> Maybe W256
-> W256
-> Transaction
Transaction ByteString
tdata Word64
gasLimit Maybe W256
gasPrice W256
nonce W256
r W256
s Maybe Addr
toAddr W256
v W256
value TxType
LegacyTransaction [] forall a. Maybe a
Nothing forall a. Maybe a
Nothing W256
1
  parseJSON Value
invalid =
    forall a. String -> Value -> Parser a
JSON.typeMismatch String
"Transaction" Value
invalid

accountAt :: Addr -> Getter (Map Addr Contract) Contract
accountAt :: Addr -> Getter (Map Addr Contract) Contract
accountAt Addr
a = (forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Addr
a) forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% (forall s a. (s -> a) -> Getter s a
to forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Contract
newAccount)

touchAccount :: Addr -> Map Addr Contract -> Map Addr Contract
touchAccount :: Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
a = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. a -> b -> a
const) Addr
a Contract
newAccount

newAccount :: Contract
newAccount :: Contract
newAccount = ContractCode -> Contract
initialContract forall a b. (a -> b) -> a -> b
$ RuntimeCode -> ContractCode
RuntimeCode (ByteString -> RuntimeCode
ConcreteRuntimeCode ByteString
"")

-- | Increments origin nonce and pays gas deposit
setupTx :: Addr -> Addr -> W256 -> Word64 -> Map Addr Contract -> Map Addr Contract
setupTx :: Addr
-> Addr -> W256 -> Word64 -> Map Addr Contract -> Map Addr Contract
setupTx Addr
origin Addr
coinbase W256
gasPrice Word64
gasLimit Map Addr Contract
prestate =
  let gasCost :: W256
gasCost = W256
gasPrice forall a. Num a => a -> a -> a
* (forall a b. (Integral a, Num b) => a -> b
num Word64
gasLimit)
  in (forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust ((forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over forall a. IsLabel "nonce" a => a
#nonce   (forall a. Num a => a -> a -> a
+ W256
1))
               forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over forall a. IsLabel "balance" a => a
#balance (forall a. Num a => a -> a -> a
subtract W256
gasCost))) Addr
origin)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
origin
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
coinbase forall a b. (a -> b) -> a -> b
$ Map Addr Contract
prestate

-- | Given a valid tx loaded into the vm state,
-- subtract gas payment from the origin, increment the nonce
-- and pay receiving address
initTx :: VM -> VM
initTx :: VM -> VM
initTx VM
vm = let
    toAddr :: Addr
toAddr   = VM
vm.state.contract
    origin :: Addr
origin   = VM
vm.tx.origin
    gasPrice :: W256
gasPrice = VM
vm.tx.gasprice
    gasLimit :: Word64
gasLimit = VM
vm.tx.gaslimit
    coinbase :: Addr
coinbase = VM
vm.block.coinbase
    value :: Expr 'EWord
value    = VM
vm.state.callvalue
    toContract :: Contract
toContract = ContractCode -> Contract
initialContract VM
vm.state.code
    preState :: Map Addr Contract
preState = Addr
-> Addr -> W256 -> Word64 -> Map Addr Contract -> Map Addr Contract
setupTx Addr
origin Addr
coinbase W256
gasPrice Word64
gasLimit VM
vm.env.contracts
    oldBalance :: W256
oldBalance = forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Addr -> Getter (Map Addr Contract) Contract
accountAt Addr
toAddr forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "balance" a => a
#balance) Map Addr Contract
preState
    creation :: Bool
creation = VM
vm.tx.isCreate
    initState :: Map Addr Contract
initState = (case Expr 'EWord -> Maybe W256
maybeLitWord Expr 'EWord
value of
      Just W256
v -> ((forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over forall a. IsLabel "balance" a => a
#balance (forall a. Num a => a -> a -> a
subtract W256
v))) Addr
origin)
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over forall a. IsLabel "balance" a => a
#balance (forall a. Num a => a -> a -> a
+ W256
v))) Addr
toAddr
      Maybe W256
Nothing -> forall a. a -> a
id)
      forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
creation
         then forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Addr
toAddr (Contract
toContract forall a b. a -> (a -> b) -> b
& forall a. IsLabel "balance" a => a
#balance forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ W256
oldBalance)
         else Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
toAddr)
      forall a b. (a -> b) -> a -> b
$ Map Addr Contract
preState

    resetConcreteStore :: Map W256 (Map W256 W256) -> Map W256 (Map W256 W256)
resetConcreteStore Map W256 (Map W256 W256)
s = if Bool
creation then forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall a b. (Integral a, Num b) => a -> b
num Addr
toAddr) forall a. Monoid a => a
mempty Map W256 (Map W256 W256)
s else Map W256 (Map W256 W256)
s

    resetStore :: Expr 'Storage -> Expr 'Storage
resetStore (ConcreteStore Map W256 (Map W256 W256)
s) = Map W256 (Map W256 W256) -> Expr 'Storage
ConcreteStore (Map W256 (Map W256 W256) -> Map W256 (Map W256 W256)
resetConcreteStore Map W256 (Map W256 W256)
s)
    resetStore (SStore a :: Expr 'EWord
a@(Lit W256
_) Expr 'EWord
k Expr 'EWord
v Expr 'Storage
s) = if Bool
creation Bool -> Bool -> Bool
&& Expr 'EWord
a forall a. Eq a => a -> a -> Bool
== (Addr -> Expr 'EWord
litAddr Addr
toAddr) then Expr 'Storage -> Expr 'Storage
resetStore Expr 'Storage
s else (Expr 'EWord
-> Expr 'EWord -> Expr 'EWord -> Expr 'Storage -> Expr 'Storage
SStore Expr 'EWord
a Expr 'EWord
k Expr 'EWord
v (Expr 'Storage -> Expr 'Storage
resetStore Expr 'Storage
s))
    resetStore (SStore {}) = forall a. HasCallStack => String -> a
error String
"cannot reset storage if it contains symbolic addresses"
    resetStore Expr 'Storage
s = Expr 'Storage
s
    in
      VM
vm forall a b. a -> (a -> b) -> b
& forall a. IsLabel "env" a => a
#env forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "contracts" a => a
#contracts forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Map Addr Contract
initState
         forall a b. a -> (a -> b) -> b
& forall a. IsLabel "tx" a => a
#tx forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "txReversion" a => a
#txReversion forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Map Addr Contract
preState
         forall a b. a -> (a -> b) -> b
& forall a. IsLabel "env" a => a
#env forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "storage" a => a
#storage forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ Expr 'Storage -> Expr 'Storage
resetStore
         forall a b. a -> (a -> b) -> b
& forall a. IsLabel "env" a => a
#env forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "origStorage" a => a
#origStorage forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ Map W256 (Map W256 W256) -> Map W256 (Map W256 W256)
resetConcreteStore