{-# Language FlexibleInstances #-}
{-# Language StrictData #-}
module EVM.Concrete where
import Prelude hiding (Word)
import EVM.RLP
import EVM.Types
import Control.Lens ((^?), ix)
import Data.Bits (Bits (..), shiftL, shiftR)
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)
import Data.Word (Word8)
import qualified Data.ByteString as BS
wordAt :: Int -> ByteString -> W256
wordAt :: Int -> ByteString -> W256
wordAt i :: Int
i bs :: ByteString
bs =
ByteString -> W256
word (Int -> ByteString -> ByteString
padRight 32 (Int -> ByteString -> ByteString
BS.drop Int
i ByteString
bs))
readByteOrZero :: Int -> ByteString -> Word8
readByteOrZero :: Int -> ByteString -> Word8
readByteOrZero i :: Int
i bs :: ByteString
bs = Word8 -> Maybe Word8 -> Word8
forall a. a -> Maybe a -> a
fromMaybe 0 (ByteString
bs ByteString -> Getting (First Word8) ByteString Word8 -> Maybe Word8
forall s a. s -> Getting (First a) s a -> Maybe a
^? Index ByteString -> Traversal' ByteString (IxValue ByteString)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index ByteString
i)
byteStringSliceWithDefaultZeroes :: Int -> Int -> ByteString -> ByteString
byteStringSliceWithDefaultZeroes :: Int -> Int -> ByteString -> ByteString
byteStringSliceWithDefaultZeroes offset :: Int
offset size :: Int
size bs :: ByteString
bs =
if Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0
then ""
else
let bs' :: ByteString
bs' = Int -> ByteString -> ByteString
BS.take Int
size (Int -> ByteString -> ByteString
BS.drop Int
offset ByteString
bs)
in ByteString
bs' ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> Word8 -> ByteString
BS.replicate (Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs') 0
wordValue :: Word -> W256
wordValue :: Word -> W256
wordValue (C _ x :: W256
x) = W256
x
sliceMemory :: (Integral a, Integral b) => a -> b -> ByteString -> ByteString
sliceMemory :: a -> b -> ByteString -> ByteString
sliceMemory o :: a
o s :: b
s =
Int -> Int -> ByteString -> ByteString
byteStringSliceWithDefaultZeroes (a -> Int
forall a b. (Integral a, Num b) => a -> b
num a
o) (b -> Int
forall a b. (Integral a, Num b) => a -> b
num b
s)
writeMemory :: ByteString -> Word -> Word -> Word -> ByteString -> ByteString
writeMemory :: ByteString -> Word -> Word -> Word -> ByteString -> ByteString
writeMemory bs1 :: ByteString
bs1 (C _ n :: W256
n) (C _ src :: W256
src) (C _ dst :: W256
dst) bs0 :: ByteString
bs0 =
let
(a :: ByteString
a, b :: ByteString
b) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
dst) ByteString
bs0
a' :: ByteString
a' = Int -> Word8 -> ByteString
BS.replicate (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
dst Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
a) 0
c :: ByteString
c = if W256
src W256 -> W256 -> Bool
forall a. Ord a => a -> a -> Bool
> Int -> W256
forall a b. (Integral a, Num b) => a -> b
num (ByteString -> Int
BS.length ByteString
bs1)
then Int -> Word8 -> ByteString
BS.replicate (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
n) 0
else W256 -> W256 -> ByteString -> ByteString
forall a b.
(Integral a, Integral b) =>
a -> b -> ByteString -> ByteString
sliceMemory W256
src W256
n ByteString
bs1
b' :: ByteString
b' = Int -> ByteString -> ByteString
BS.drop (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
n) ByteString
b
in
ByteString
a ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
a' ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
c ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
b'
readMemoryWord :: Word -> ByteString -> Word
readMemoryWord :: Word -> ByteString -> Word
readMemoryWord (C _ i :: W256
i) m :: ByteString
m =
if W256
i W256 -> W256 -> Bool
forall a. Ord a => a -> a -> Bool
> (Int -> W256
forall a b. (Integral a, Num b) => a -> b
num (Int -> W256) -> Int -> W256
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
BS.length ByteString
m) then 0 else
let
go :: W256 -> Int -> W256
go !W256
a (-1) = W256
a
go !W256
a !Int
n = W256 -> Int -> W256
go (W256
a W256 -> W256 -> W256
forall a. Num a => a -> a -> a
+ W256 -> Int -> W256
forall a. Bits a => a -> Int -> a
shiftL (Word8 -> W256
forall a b. (Integral a, Num b) => a -> b
num (Word8 -> W256) -> Word8 -> W256
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> Word8
readByteOrZero (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) ByteString
m)
(8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (31 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n))) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1)
w :: W256
w = W256 -> Int -> W256
go (0 :: W256) (31 :: Int)
in {-# SCC "readMemoryWord" #-}
Whiff -> W256 -> Word
C (W256 -> Whiff
Literal W256
w) W256
w
readMemoryWord32 :: Word -> ByteString -> Word
readMemoryWord32 :: Word -> ByteString -> Word
readMemoryWord32 (C _ i :: W256
i) m :: ByteString
m =
let
go :: W256 -> Int -> W256
go !W256
a (-1) = W256
a
go !W256
a !Int
n = W256 -> Int -> W256
go (W256
a W256 -> W256 -> W256
forall a. Num a => a -> a -> a
+ W256 -> Int -> W256
forall a. Bits a => a -> Int -> a
shiftL (Word8 -> W256
forall a b. (Integral a, Num b) => a -> b
num (Word8 -> W256) -> Word8 -> W256
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> Word8
readByteOrZero (W256 -> Int
forall a b. (Integral a, Num b) => a -> b
num W256
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) ByteString
m)
(8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (3 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n))) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1)
in {-# SCC "readMemoryWord32" #-}
W256 -> Word
w256 (W256 -> Word) -> W256 -> Word
forall a b. (a -> b) -> a -> b
$ W256 -> Int -> W256
go (0 :: W256) (3 :: Int)
setMemoryWord :: Word -> Word -> ByteString -> ByteString
setMemoryWord :: Word -> Word -> ByteString -> ByteString
setMemoryWord (C _ i :: W256
i) (C _ x :: W256
x) =
ByteString -> Word -> Word -> Word -> ByteString -> ByteString
writeMemory (W256 -> ByteString
word256Bytes W256
x) 32 0 (W256 -> Word
forall a b. (Integral a, Num b) => a -> b
num W256
i)
setMemoryByte :: Word -> Word8 -> ByteString -> ByteString
setMemoryByte :: Word -> Word8 -> ByteString -> ByteString
setMemoryByte (C _ i :: W256
i) x :: Word8
x =
ByteString -> Word -> Word -> Word -> ByteString -> ByteString
writeMemory (Word8 -> ByteString
BS.singleton Word8
x) 1 0 (W256 -> Word
forall a b. (Integral a, Num b) => a -> b
num W256
i)
keccakBlob :: ByteString -> Word
keccakBlob :: ByteString -> Word
keccakBlob x :: ByteString
x = Whiff -> W256 -> Word
C (Buffer -> Whiff
FromKeccak (ByteString -> Buffer
ConcreteBuffer ByteString
x)) (ByteString -> W256
keccak ByteString
x)
(^) :: W256 -> W256 -> W256
x0 :: W256
x0 ^ :: W256 -> W256 -> W256
^ y0 :: W256
y0 | W256
y0 W256 -> W256 -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = [Char] -> W256
forall a. [Char] -> a
errorWithoutStackTrace "Negative exponent"
| W256
y0 W256 -> W256 -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = 1
| Bool
otherwise = W256 -> W256 -> W256
forall a a. (Bits a, Num a, Num a) => a -> a -> a
f W256
x0 W256
y0
where
f :: a -> a -> a
f x :: a
x y :: a
y | Bool -> Bool
not (a -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit a
y 0) = a -> a -> a
f (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (a
y a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` 1)
| a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== 1 = a
x
| Bool
otherwise = a -> a -> a -> a
forall a a. (Bits a, Num a, Num a) => a -> a -> a -> a
g (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) ((a
y a -> a -> a
forall a. Num a => a -> a -> a
- 1) a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` 1) a
x
g :: a -> a -> a -> a
g x :: a
x y :: a
y z :: a
z | Bool -> Bool
not (a -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit a
y 0) = a -> a -> a -> a
g (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (a
y a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` 1) a
z
| a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== 1 = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
z
| Bool
otherwise = a -> a -> a -> a
g (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) ((a
y a -> a -> a
forall a. Num a => a -> a -> a
- 1) a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` 1) (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
z)
createAddress :: Addr -> W256 -> Addr
createAddress :: Addr -> W256 -> Addr
createAddress a :: Addr
a n :: W256
n = W256 -> Addr
forall a b. (Integral a, Num b) => a -> b
num (W256 -> Addr) -> W256 -> Addr
forall a b. (a -> b) -> a -> b
$ ByteString -> W256
keccak (ByteString -> W256) -> ByteString -> W256
forall a b. (a -> b) -> a -> b
$ [RLP] -> ByteString
rlpList [Addr -> RLP
rlpAddrFull Addr
a, W256 -> RLP
rlpWord256 W256
n]
create2Address :: Addr -> W256 -> ByteString -> Addr
create2Address :: Addr -> W256 -> ByteString -> Addr
create2Address a :: Addr
a s :: W256
s b :: ByteString
b = W256 -> Addr
forall a b. (Integral a, Num b) => a -> b
num (W256 -> Addr) -> W256 -> Addr
forall a b. (a -> b) -> a -> b
$ ByteString -> W256
keccak (ByteString -> W256) -> ByteString -> W256
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
[Word8 -> ByteString
BS.singleton 0xff, Addr -> ByteString
word160Bytes Addr
a, W256 -> ByteString
word256Bytes (W256 -> ByteString) -> W256 -> ByteString
forall a b. (a -> b) -> a -> b
$ W256 -> W256
forall a b. (Integral a, Num b) => a -> b
num W256
s, W256 -> ByteString
word256Bytes (W256 -> ByteString) -> W256 -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> W256
keccak ByteString
b]