module EVM.Transaction where

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.Aeson (FromJSON (..))
import Data.Aeson qualified as JSON
import Data.Aeson.Types qualified as JSON
import Data.ByteString (ByteString, cons)
import Data.ByteString qualified as BS
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Maybe (fromMaybe, isNothing, fromJust)
import Data.Word (Word64)
import GHC.Generics (Generic)
import Numeric (showHex)
import Witch (into, unsafeInto)

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

instance JSON.ToJSON AccessListEntry

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

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

emptyTransaction :: Transaction
emptyTransaction :: Transaction
emptyTransaction = Transaction { $sel:txdata:Transaction :: ByteString
txdata = ByteString
forall a. Monoid a => a
mempty
                               , $sel:gasLimit:Transaction :: Word64
gasLimit = Word64
0
                               , $sel:gasPrice:Transaction :: Maybe W256
gasPrice = Maybe W256
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 = Maybe Addr
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 = Maybe W256
forall a. Maybe a
Nothing
                               , $sel:maxFeePerGas:Transaction :: Maybe W256
maxFeePerGas = Maybe W256
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 = ((([W256] -> [W256] -> [W256]) -> [(Addr, [W256])] -> Map Addr [W256]
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith [W256] -> [W256] -> [W256]
forall a. [a] -> [a] -> [a]
(++)) ([(Addr, [W256])] -> Map Addr [W256])
-> ([AccessListEntry] -> [(Addr, [W256])])
-> [AccessListEntry]
-> Map Addr [W256]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AccessListEntry] -> [(Addr, [W256])]
makeTups) Transaction
tx.accessList
  where makeTups :: [AccessListEntry] -> [(Addr, [W256])]
makeTups = (AccessListEntry -> (Addr, [W256]))
-> [AccessListEntry] -> [(Addr, [W256])]
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 W256 -> W256 -> Bool
forall a. Eq a => a -> a -> Bool
== W256
27 Bool -> Bool -> Bool
|| W256
v W256 -> W256 -> Bool
forall a. Eq a => a -> a -> Bool
== W256
28 then W256
v
               else W256
27 W256 -> W256 -> W256
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 = Word8 -> W256
forall target source. From source target => source -> target
into Word8
v, $sel:r:Transaction :: W256
r = W256
r, $sel:s:Transaction :: W256
s = W256
s}
  where
    hash :: W256
hash = ByteString -> W256
keccak' (ByteString -> W256) -> ByteString -> W256
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 W256 -> W256 -> Bool
forall a. Eq a => a -> a -> Bool
== (Transaction
tx.chainId W256 -> W256 -> W256
forall a. Num a => a -> a -> a
* W256
2 W256 -> W256 -> W256
forall a. Num a => a -> a -> a
+ W256
35) Bool -> Bool -> Bool
|| W256
v W256 -> W256 -> Bool
forall a. Eq a => a -> a -> Bool
== (Transaction
tx.chainId W256 -> W256 -> W256
forall a. Num a => a -> a -> a
* W256
2 W256 -> W256 -> W256
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          = Transaction
tx.v
        to' :: RLP
to'        = case Transaction
tx.toAddr of
          Just Addr
a  -> ByteString -> RLP
BS (ByteString -> RLP) -> ByteString -> RLP
forall a b. (a -> b) -> a -> b
$ Addr -> ByteString
word160Bytes Addr
a
          Maybe Addr
Nothing -> ByteString -> RLP
BS ByteString
forall a. Monoid a => a
mempty
        maxFee :: W256
maxFee = Maybe W256 -> W256
forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.maxFeePerGas
        maxPrio :: W256
maxPrio = Maybe W256 -> W256
forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.maxPriorityFeeGas
        gasPrice :: W256
gasPrice = Maybe W256 -> W256
forall a. HasCallStack => Maybe a -> a
fromJust Transaction
tx.gasPrice
        accessList :: [AccessListEntry]
accessList = Transaction
tx.accessList
        rlpAccessList :: RLP
rlpAccessList = [RLP] -> RLP
EVM.RLP.List ([RLP] -> RLP) -> [RLP] -> RLP
forall a b. (a -> b) -> a -> b
$ (AccessListEntry -> RLP) -> [AccessListEntry] -> [RLP]
forall a b. (a -> b) -> [a] -> [b]
map (\AccessListEntry
accessEntry ->
          [RLP] -> RLP
EVM.RLP.List [ByteString -> RLP
BS (ByteString -> RLP) -> ByteString -> RLP
forall a b. (a -> b) -> a -> b
$ Addr -> ByteString
word160Bytes AccessListEntry
accessEntry.address,
                        [RLP] -> RLP
EVM.RLP.List ([RLP] -> RLP) -> [RLP] -> RLP
forall a b. (a -> b) -> a -> b
$ (W256 -> RLP) -> [W256] -> [RLP]
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 (Word64 -> W256
forall target source. From source target => source -> target
into 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 (Word64 -> W256
forall target source. From source target => source -> target
into 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 (ByteString -> ByteString) -> ByteString -> ByteString
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 (Word64 -> W256
forall target source. From source target => source -> target
into 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 (ByteString -> ByteString) -> ByteString -> ByteString
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 (Word64 -> W256
forall target source. From source target => source -> target
into 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 =
    [Word64] -> Word64
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((AccessListEntry -> Word64) -> [AccessListEntry] -> [Word64]
forall a b. (a -> b) -> [a] -> [b]
map
      (\AccessListEntry
ale ->
        FeeSchedule Word64
fs.g_access_list_address  Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+
        (FeeSchedule Word64
fs.g_access_list_storage_key  Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* (Int -> Word64
forall target source.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
unsafeInto (Int -> Word64) -> ([W256] -> Int) -> [W256] -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [W256] -> Int
forall a. [a] -> Int
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 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
zeroBytes
      baseCost :: Word64
baseCost     = FeeSchedule Word64
fs.g_transaction
        Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ (if Maybe Addr -> Bool
forall a. Maybe a -> Bool
isNothing Transaction
tx.toAddr then FeeSchedule Word64
fs.g_txcreate Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
initcodeCost else Word64
0)
        Word64 -> Word64 -> Word64
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 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Int -> Word64
forall target source.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
unsafeInto (Int -> Int -> Int
forall a. (Num a, Integral a) => a -> a -> a
ceilDiv (ByteString -> Int
BS.length ByteString
calldata) Int
32)
  in Word64
baseCost Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
zeroCost Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* (Int -> Word64
forall target source.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
unsafeInto Int
zeroBytes) Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
nonZeroCost Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* (Int -> Word64
forall target source.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
unsafeInto 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 Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"storageKeys") Parser Value -> (Value -> Parser [W256]) -> Parser [W256]
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser [W256]
forall a. FromJSON a => Value -> Parser [a]
parseJSONList
    AccessListEntry -> Parser AccessListEntry
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccessListEntry -> Parser AccessListEntry)
-> AccessListEntry -> Parser AccessListEntry
forall a b. (a -> b) -> a -> b
$ Addr -> [W256] -> AccessListEntry
AccessListEntry Addr
accessAddress_ [W256]
accessStorageKeys_
  parseJSON Value
invalid =
    String -> Value -> Parser AccessListEntry
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 (Text -> ByteString) -> Parser Text -> Parser ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
val Object -> Key -> Parser Text
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 <- (String -> W256) -> Maybe String -> Maybe W256
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> W256
forall a. Read a => String -> a
read (Maybe String -> Maybe W256)
-> Parser (Maybe String) -> Parser (Maybe W256)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"gasPrice"
    Maybe W256
maxPrio  <- (String -> W256) -> Maybe String -> Maybe W256
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> W256
forall a. Read a => String -> a
read (Maybe String -> Maybe W256)
-> Parser (Maybe String) -> Parser (Maybe W256)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"maxPriorityFeePerGas"
    Maybe W256
maxFee   <- (String -> W256) -> Maybe String -> Maybe W256
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> W256
forall a. Read a => String -> a
read (Maybe String -> Maybe W256)
-> Parser (Maybe String) -> Parser (Maybe W256)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
val Object -> Key -> Parser (Maybe String)
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   <- (String -> Int) -> Maybe String -> Maybe Int
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> Int
forall a. Read a => String -> a
read :: String -> Int) (Maybe String -> Maybe Int)
-> Parser (Maybe String) -> Parser (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
val Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
JSON..:? Key
"type")
    case Maybe Int
txType of
      Just Int
0x00 -> Transaction -> Parser Transaction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Transaction -> Parser Transaction)
-> Transaction -> Parser Transaction
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 [] Maybe W256
forall a. Maybe a
Nothing Maybe W256
forall a. Maybe a
Nothing W256
1
      Just Int
0x01 -> do
        [AccessListEntry]
accessListEntries <- (Object
val Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"accessList") Parser Value
-> (Value -> Parser [AccessListEntry]) -> Parser [AccessListEntry]
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser [AccessListEntry]
forall a. FromJSON a => Value -> Parser [a]
parseJSONList
        Transaction -> Parser Transaction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Transaction -> Parser Transaction)
-> Transaction -> Parser Transaction
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 Maybe W256
forall a. Maybe a
Nothing Maybe W256
forall a. Maybe a
Nothing W256
1
      Just Int
0x02 -> do
        [AccessListEntry]
accessListEntries <- (Object
val Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
JSON..: Key
"accessList") Parser Value
-> (Value -> Parser [AccessListEntry]) -> Parser [AccessListEntry]
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser [AccessListEntry]
forall a. FromJSON a => Value -> Parser [a]
parseJSONList
        Transaction -> Parser Transaction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Transaction -> Parser Transaction)
-> Transaction -> Parser Transaction
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
_ -> String -> Parser Transaction
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unrecognized custom transaction type"
      Maybe Int
Nothing -> Transaction -> Parser Transaction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Transaction -> Parser Transaction)
-> Transaction -> Parser Transaction
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 [] Maybe W256
forall a. Maybe a
Nothing Maybe W256
forall a. Maybe a
Nothing W256
1
  parseJSON Value
invalid =
    String -> Value -> Parser Transaction
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 = (Index (Map Addr Contract)
-> Lens' (Map Addr Contract) (Maybe (IxValue (Map Addr Contract)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index (Map Addr Contract)
Addr
a) Optic
  A_Lens
  NoIx
  (Map Addr Contract)
  (Map Addr Contract)
  (Maybe Contract)
  (Maybe Contract)
-> Optic
     A_Getter NoIx (Maybe Contract) (Maybe Contract) Contract Contract
-> Getter (Map Addr Contract) Contract
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
% ((Maybe Contract -> Contract)
-> Optic
     A_Getter NoIx (Maybe Contract) (Maybe Contract) Contract Contract
forall s a. (s -> a) -> Getter s a
to ((Maybe Contract -> Contract)
 -> Optic
      A_Getter NoIx (Maybe Contract) (Maybe Contract) Contract Contract)
-> (Maybe Contract -> Contract)
-> Optic
     A_Getter NoIx (Maybe Contract) (Maybe Contract) Contract Contract
forall a b. (a -> b) -> a -> b
$ Contract -> Maybe Contract -> Contract
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 = (Contract -> Contract -> Contract)
-> Addr -> Contract -> Map Addr Contract -> Map Addr Contract
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith ((Contract -> Contract -> Contract)
-> Contract -> Contract -> Contract
forall a b c. (a -> b -> c) -> b -> a -> c
flip Contract -> Contract -> Contract
forall a b. a -> b -> a
const) Addr
a Contract
newAccount

newAccount :: Contract
newAccount :: Contract
newAccount = ContractCode -> Contract
initialContract (ContractCode -> Contract) -> ContractCode -> Contract
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 W256 -> W256 -> W256
forall a. Num a => a -> a -> a
* (Word64 -> W256
forall target source. From source target => source -> target
into Word64
gasLimit)
  in ((Contract -> Contract)
-> Addr -> Map Addr Contract -> Map Addr Contract
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust ((Optic A_Lens NoIx Contract Contract W256 W256
-> (W256 -> W256) -> Contract -> Contract
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic A_Lens NoIx Contract Contract W256 W256
#nonce   (W256 -> W256 -> W256
forall a. Num a => a -> a -> a
+ W256
1))
               (Contract -> Contract)
-> (Contract -> Contract) -> Contract -> Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Optic A_Lens NoIx Contract Contract W256 W256
-> (W256 -> W256) -> Contract -> Contract
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic A_Lens NoIx Contract Contract W256 W256
#balance (W256 -> W256 -> W256
forall a. Num a => a -> a -> a
subtract W256
gasCost))) Addr
origin)
    (Map Addr Contract -> Map Addr Contract)
-> (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract
-> Map Addr Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
origin
    (Map Addr Contract -> Map Addr Contract)
-> (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract
-> Map Addr Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr -> Map Addr Contract -> Map Addr Contract
touchAccount Addr
coinbase (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract -> Map Addr Contract
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 = Optic' A_Getter NoIx (Map Addr Contract) W256
-> Map Addr Contract -> W256
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 Getter (Map Addr Contract) Contract
-> Optic A_Lens NoIx Contract Contract W256 W256
-> Optic' A_Getter NoIx (Map Addr Contract) W256
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
% Optic A_Lens NoIx Contract Contract W256 W256
#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 -> (((Contract -> Contract)
-> Addr -> Map Addr Contract -> Map Addr Contract
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (Optic A_Lens NoIx Contract Contract W256 W256
-> (W256 -> W256) -> Contract -> Contract
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic A_Lens NoIx Contract Contract W256 W256
#balance (W256 -> W256 -> W256
forall a. Num a => a -> a -> a
subtract W256
v))) Addr
origin)
              (Map Addr Contract -> Map Addr Contract)
-> (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract
-> Map Addr Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Contract -> Contract)
-> Addr -> Map Addr Contract -> Map Addr Contract
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (Optic A_Lens NoIx Contract Contract W256 W256
-> (W256 -> W256) -> Contract -> Contract
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic A_Lens NoIx Contract Contract W256 W256
#balance (W256 -> W256 -> W256
forall a. Num a => a -> a -> a
+ W256
v))) Addr
toAddr
      Maybe W256
Nothing -> Map Addr Contract -> Map Addr Contract
forall a. a -> a
id)
      (Map Addr Contract -> Map Addr Contract)
-> (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract
-> Map Addr Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
creation
         then Addr -> Contract -> Map Addr Contract -> Map Addr Contract
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Addr
toAddr (Contract
toContract Contract -> (Contract -> Contract) -> Contract
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx Contract Contract W256 W256
#balance Optic A_Lens NoIx Contract Contract W256 W256
-> W256 -> Contract -> Contract
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)
      (Map Addr Contract -> Map Addr Contract)
-> Map Addr Contract -> Map Addr Contract
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 W256
-> Map W256 W256
-> Map W256 (Map W256 W256)
-> Map W256 (Map W256 W256)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (Addr -> W256
forall target source. From source target => source -> target
into Addr
toAddr) Map W256 W256
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 Expr 'EWord -> Expr 'EWord -> Bool
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 {}) = String -> Expr 'Storage
forall a. HasCallStack => String -> a
internalError String
"cannot reset storage if it contains symbolic addresses"
    resetStore Expr 'Storage
s = Expr 'Storage
s
    in
      VM
vm VM -> (VM -> VM) -> VM
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx VM VM Env Env
#env Optic A_Lens NoIx VM VM Env Env
-> Optic
     A_Lens NoIx Env Env (Map Addr Contract) (Map Addr Contract)
-> Optic A_Lens NoIx VM VM (Map Addr Contract) (Map Addr Contract)
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
% Optic A_Lens NoIx Env Env (Map Addr Contract) (Map Addr Contract)
#contracts Optic A_Lens NoIx VM VM (Map Addr Contract) (Map Addr Contract)
-> Map Addr Contract -> VM -> VM
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
         VM -> (VM -> VM) -> VM
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx VM VM TxState TxState
#tx Optic A_Lens NoIx VM VM TxState TxState
-> Optic
     A_Lens NoIx TxState TxState (Map Addr Contract) (Map Addr Contract)
-> Optic A_Lens NoIx VM VM (Map Addr Contract) (Map Addr Contract)
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
% Optic
  A_Lens NoIx TxState TxState (Map Addr Contract) (Map Addr Contract)
#txReversion Optic A_Lens NoIx VM VM (Map Addr Contract) (Map Addr Contract)
-> Map Addr Contract -> VM -> VM
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
         VM -> (VM -> VM) -> VM
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx VM VM Env Env
#env Optic A_Lens NoIx VM VM Env Env
-> Optic A_Lens NoIx Env Env (Expr 'Storage) (Expr 'Storage)
-> Optic A_Lens NoIx VM VM (Expr 'Storage) (Expr 'Storage)
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
% Optic A_Lens NoIx Env Env (Expr 'Storage) (Expr 'Storage)
#storage Optic A_Lens NoIx VM VM (Expr 'Storage) (Expr 'Storage)
-> (Expr 'Storage -> Expr 'Storage) -> VM -> VM
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
         VM -> (VM -> VM) -> VM
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx VM VM Env Env
#env Optic A_Lens NoIx VM VM Env Env
-> Optic
     A_Lens
     NoIx
     Env
     Env
     (Map W256 (Map W256 W256))
     (Map W256 (Map W256 W256))
-> Optic
     A_Lens
     NoIx
     VM
     VM
     (Map W256 (Map W256 W256))
     (Map W256 (Map W256 W256))
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
% Optic
  A_Lens
  NoIx
  Env
  Env
  (Map W256 (Map W256 W256))
  (Map W256 (Map W256 W256))
#origStorage Optic
  A_Lens
  NoIx
  VM
  VM
  (Map W256 (Map W256 W256))
  (Map W256 (Map W256 W256))
-> (Map W256 (Map W256 W256) -> Map W256 (Map W256 W256))
-> VM
-> VM
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