module EVM.Transaction where

import Prelude hiding (Word)

import qualified EVM
import EVM (balance, initialContract)
import EVM.FeeSchedule
import EVM.Precompiled (execute)
import EVM.RLP
import EVM.Types
import EVM.Expr (litAddr)

import Control.Lens

import Data.Aeson (FromJSON (..))
import Data.ByteString (ByteString)
import Data.Map (Map)
import Data.Maybe (fromMaybe, isNothing, fromJust)

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)

data AccessListEntry = AccessListEntry {
  AccessListEntry -> Addr
accessAddress :: Addr,
  AccessListEntry -> [W256]
accessStorageKeys :: [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

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)

data Transaction = Transaction {
    Transaction -> ByteString
txData     :: ByteString,
    Transaction -> Word64
txGasLimit :: Word64,
    Transaction -> Maybe W256
txGasPrice :: Maybe W256,
    Transaction -> W256
txNonce    :: W256,
    Transaction -> W256
txR        :: W256,
    Transaction -> W256
txS        :: W256,
    Transaction -> Maybe Addr
txToAddr   :: Maybe Addr,
    Transaction -> W256
txV        :: W256,
    Transaction -> W256
txValue    :: W256,
    Transaction -> TxType
txType     :: TxType,
    Transaction -> [AccessListEntry]
txAccessList :: [AccessListEntry],
    Transaction -> Maybe W256
txMaxPriorityFeeGas :: Maybe W256,
    Transaction -> Maybe W256
txMaxFeePerGas :: Maybe 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

-- | 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) forall a b. (a -> b) -> a -> b
$ Transaction -> [AccessListEntry]
txAccessList Transaction
tx
  where makeTups :: [AccessListEntry] -> [(Addr, [W256])]
makeTups = forall a b. (a -> b) -> [a] -> [b]
map (\AccessListEntry
ale -> (AccessListEntry -> Addr
accessAddress AccessListEntry
ale, AccessListEntry -> [W256]
accessStorageKeys AccessListEntry
ale))

ecrec :: W256 -> W256 -> W256 -> W256 -> Maybe Addr
ecrec :: W256 -> W256 -> W256 -> W256 -> Maybe Addr
ecrec W256
v W256
r W256
s W256
e = forall a b. (Integral a, Num b) => a -> b
num forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> W256
word forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ByteString -> Int -> Maybe ByteString
EVM.Precompiled.execute Int
1 ByteString
input Int
32
  where input :: ByteString
input = [ByteString] -> ByteString
BS.concat (W256 -> ByteString
word256Bytes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [W256
e, W256
v, W256
r, W256
s])

sender :: Int -> Transaction -> Maybe Addr
sender :: Int -> Transaction -> Maybe Addr
sender Int
chainId Transaction
tx = W256 -> W256 -> W256 -> W256 -> Maybe Addr
ecrec W256
v' (Transaction -> W256
txR Transaction
tx) (Transaction -> W256
txS Transaction
tx) W256
hash
  where hash :: W256
hash = ByteString -> W256
keccak' (Int -> Transaction -> ByteString
signingData Int
chainId Transaction
tx)
        v :: W256
v    = Transaction -> W256
txV Transaction
tx
        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

signingData :: Int -> Transaction -> ByteString
signingData :: Int -> Transaction -> ByteString
signingData Int
chainId Transaction
tx =
  case Transaction -> TxType
txType Transaction
tx of
    TxType
LegacyTransaction -> if Int
v forall a. Eq a => a -> a -> Bool
== (Int
chainId forall a. Num a => a -> a -> a
* Int
2 forall a. Num a => a -> a -> a
+ Int
35) Bool -> Bool -> Bool
|| Int
v forall a. Eq a => a -> a -> Bool
== (Int
chainId forall a. Num a => a -> a -> a
* Int
2 forall a. Num a => a -> a -> a
+ Int
36)
      then ByteString
eip155Data
      else ByteString
normalData
    TxType
AccessListTransaction -> ByteString
eip2930Data
    TxType
EIP1559Transaction -> ByteString
eip1559Data
  where v :: Int
v          = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Transaction -> W256
txV Transaction
tx)
        to' :: RLP
to'        = case Transaction -> Maybe Addr
txToAddr Transaction
tx 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 forall a b. (a -> b) -> a -> b
$ Transaction -> Maybe W256
txMaxFeePerGas Transaction
tx
        maxPrio :: W256
maxPrio = forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Transaction -> Maybe W256
txMaxPriorityFeeGas Transaction
tx
        gasPrice :: W256
gasPrice = forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Transaction -> Maybe W256
txGasPrice Transaction
tx
        accessList :: [AccessListEntry]
accessList = Transaction -> [AccessListEntry]
txAccessList Transaction
tx
        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 -> Addr
accessAddress AccessListEntry
accessEntry),
                        [RLP] -> RLP
EVM.RLP.List forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map W256 -> RLP
rlpWordFull forall a b. (a -> b) -> a -> b
$ AccessListEntry -> [W256]
accessStorageKeys AccessListEntry
accessEntry]
          ) [AccessListEntry]
accessList
        normalData :: ByteString
normalData = [RLP] -> ByteString
rlpList [W256 -> RLP
rlpWord256 (Transaction -> W256
txNonce Transaction
tx),
                              W256 -> RLP
rlpWord256 W256
gasPrice,
                              W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num forall a b. (a -> b) -> a -> b
$ Transaction -> Word64
txGasLimit Transaction
tx),
                              RLP
to',
                              W256 -> RLP
rlpWord256 (Transaction -> W256
txValue Transaction
tx),
                              ByteString -> RLP
BS (Transaction -> ByteString
txData Transaction
tx)]
        eip155Data :: ByteString
eip155Data = [RLP] -> ByteString
rlpList [W256 -> RLP
rlpWord256 (Transaction -> W256
txNonce Transaction
tx),
                              W256 -> RLP
rlpWord256 W256
gasPrice,
                              W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num forall a b. (a -> b) -> a -> b
$ Transaction -> Word64
txGasLimit Transaction
tx),
                              RLP
to',
                              W256 -> RLP
rlpWord256 (Transaction -> W256
txValue Transaction
tx),
                              ByteString -> RLP
BS (Transaction -> ByteString
txData Transaction
tx),
                              W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
chainId),
                              W256 -> RLP
rlpWord256 W256
0x0,
                              W256 -> RLP
rlpWord256 W256
0x0]
        eip1559Data :: ByteString
eip1559Data = forall s a. Cons s s a a => a -> s -> s
cons Word8
0x02 forall a b. (a -> b) -> a -> b
$ [RLP] -> ByteString
rlpList [
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
chainId),
          W256 -> RLP
rlpWord256 (Transaction -> W256
txNonce Transaction
tx),
          W256 -> RLP
rlpWord256 W256
maxPrio,
          W256 -> RLP
rlpWord256 W256
maxFee,
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num forall a b. (a -> b) -> a -> b
$ Transaction -> Word64
txGasLimit Transaction
tx),
          RLP
to',
          W256 -> RLP
rlpWord256 (Transaction -> W256
txValue Transaction
tx),
          ByteString -> RLP
BS (Transaction -> ByteString
txData Transaction
tx),
          RLP
rlpAccessList]

        eip2930Data :: ByteString
eip2930Data = forall s a. Cons s s a a => a -> s -> s
cons Word8
0x01 forall a b. (a -> b) -> a -> b
$ [RLP] -> ByteString
rlpList [
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
chainId),
          W256 -> RLP
rlpWord256 (Transaction -> W256
txNonce Transaction
tx),
          W256 -> RLP
rlpWord256 W256
gasPrice,
          W256 -> RLP
rlpWord256 (forall a b. (Integral a, Num b) => a -> b
num forall a b. (a -> b) -> a -> b
$ Transaction -> Word64
txGasLimit Transaction
tx),
          RLP
to',
          W256 -> RLP
rlpWord256 (Transaction -> W256
txValue Transaction
tx),
          ByteString -> RLP
BS (Transaction -> ByteString
txData Transaction
tx),
          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 ->
        forall n. FeeSchedule n -> n
g_access_list_address FeeSchedule Word64
fs forall a. Num a => a -> a -> a
+
        (forall n. FeeSchedule n -> n
g_access_list_storage_key FeeSchedule Word64
fs 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 -> [W256]
accessStorageKeys AccessListEntry
ale)))
        [AccessListEntry]
al)

txGasCost :: FeeSchedule Word64 -> Transaction -> Word64
txGasCost :: FeeSchedule Word64 -> Transaction -> Word64
txGasCost FeeSchedule Word64
fs Transaction
tx =
  let calldata :: ByteString
calldata     = Transaction -> ByteString
txData Transaction
tx
      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     = forall n. FeeSchedule n -> n
g_transaction FeeSchedule Word64
fs
        forall a. Num a => a -> a -> a
+ (if forall a. Maybe a -> Bool
isNothing (Transaction -> Maybe Addr
txToAddr Transaction
tx) then forall n. FeeSchedule n -> n
g_txcreate FeeSchedule Word64
fs else Word64
0)
        forall a. Num a => a -> a -> a
+ (FeeSchedule Word64 -> [AccessListEntry] -> Word64
accessListPrice FeeSchedule Word64
fs forall a b. (a -> b) -> a -> b
$ Transaction -> [AccessListEntry]
txAccessList Transaction
tx)
      zeroCost :: Word64
zeroCost     = forall n. FeeSchedule n -> n
g_txdatazero FeeSchedule Word64
fs
      nonZeroCost :: Word64
nonZeroCost  = forall n. FeeSchedule n -> n
g_txdatanonzero FeeSchedule Word64
fs
  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    <- Object -> Key -> Parser ByteString
dataField Object
val 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
-> 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
      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
-> 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
      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
-> 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
      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
-> 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
  parseJSON Value
invalid =
    forall a. String -> Value -> Parser a
JSON.typeMismatch String
"Transaction" Value
invalid

accountAt :: Addr -> Getter (Map Addr EVM.Contract) EVM.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 b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Contract
newAccount)

touchAccount :: Addr -> Map Addr EVM.Contract -> Map Addr EVM.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 :: EVM.Contract
newAccount :: Contract
newAccount = ContractCode -> Contract
initialContract forall a b. (a -> b) -> a -> b
$ RuntimeCode -> ContractCode
EVM.RuntimeCode (ByteString -> RuntimeCode
EVM.ConcreteRuntimeCode ByteString
"")

-- | Increments origin nonce and pays gas deposit
setupTx :: Addr -> Addr -> W256 -> Word64 -> Map Addr EVM.Contract -> Map Addr EVM.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 s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Contract W256
EVM.nonce   (forall a. Num a => a -> a -> a
+ W256
1))
               forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Contract W256
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 :: EVM.VM -> EVM.VM
initTx :: VM -> VM
initTx VM
vm = let
    toAddr :: Addr
toAddr   = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM FrameState
EVM.state forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' FrameState Addr
EVM.contract) VM
vm
    origin :: Addr
origin   = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM TxState
EVM.tx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' TxState Addr
EVM.origin) VM
vm
    gasPrice :: W256
gasPrice = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM TxState
EVM.tx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' TxState W256
EVM.gasprice) VM
vm
    gasLimit :: Word64
gasLimit = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM TxState
EVM.tx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' TxState Word64
EVM.txgaslimit) VM
vm
    coinbase :: Addr
coinbase = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM Block
EVM.block forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Block Addr
EVM.coinbase) VM
vm
    value :: Expr 'EWord
value    = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM FrameState
EVM.state forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' FrameState (Expr 'EWord)
EVM.callvalue) VM
vm
    toContract :: Contract
toContract = ContractCode -> Contract
initialContract (forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM FrameState
EVM.state forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' FrameState ContractCode
EVM.code) VM
vm)
    preState :: Map Addr Contract
preState = Addr
-> Addr -> W256 -> Word64 -> Map Addr Contract -> Map Addr Contract
setupTx Addr
origin Addr
coinbase W256
gasPrice Word64
gasLimit forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM Env
EVM.env forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Env (Map Addr Contract)
EVM.contracts) VM
vm
    oldBalance :: W256
oldBalance = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Addr -> Getter (Map Addr Contract) Contract
accountAt Addr
toAddr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Contract W256
balance) Map Addr Contract
preState
    creation :: Bool
creation = forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Lens' VM TxState
EVM.tx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' TxState Bool
EVM.isCreate) VM
vm
    initState :: Map Addr Contract
initState = (case Expr 'EWord -> Maybe W256
unlit Expr 'EWord
value of
      Just W256
v -> ((forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Contract W256
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 s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Contract W256
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
& Lens' Contract W256
balance forall s t a b. ASetter 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
& Lens' VM Env
EVM.env forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Env (Map Addr Contract)
EVM.contracts forall s t a b. ASetter s t a b -> b -> s -> t
.~ Map Addr Contract
initState
         forall a b. a -> (a -> b) -> b
& Lens' VM TxState
EVM.tx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' TxState (Map Addr Contract)
EVM.txReversion forall s t a b. ASetter s t a b -> b -> s -> t
.~ Map Addr Contract
preState
         forall a b. a -> (a -> b) -> b
& Lens' VM Env
EVM.env forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Env (Expr 'Storage)
EVM.storage forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Expr 'Storage -> Expr 'Storage
resetStore
         forall a b. a -> (a -> b) -> b
& Lens' VM Env
EVM.env forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Env (Map W256 (Map W256 W256))
EVM.origStorage forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Map W256 (Map W256 W256) -> Map W256 (Map W256 W256)
resetConcreteStore