{-|
Module      : Helper functions to sign a transaction and derive address from
Description :        for the EVM given a secret key
-}

module EVM.Sign where

import qualified Crypto.Hash as Crypto
import Data.Maybe (fromMaybe)
import Crypto.PubKey.ECC.ECDSA (signDigestWith, PrivateKey(..), Signature(..))
import Crypto.PubKey.ECC.Types (getCurveByName, CurveName(..), Point(..))
import Crypto.PubKey.ECC.Generate (generateQ)

import EVM.ABI (encodeAbiValue, AbiValue(..))
import qualified Data.ByteString   as BS
import EVM.Types
import EVM.Expr (exprToAddr)
import EVM.Precompiled
import Data.Word


-- Given a secret key, generates the address
deriveAddr :: Integer -> Maybe Addr
deriveAddr :: Integer -> Maybe Addr
deriveAddr Integer
sk = case Point
pubPoint of
           Point
PointO -> forall a. Maybe a
Nothing
           Point Integer
x Integer
y ->
             -- See yellow paper #286
               let pub :: ByteString
pub = [ByteString] -> ByteString
BS.concat [ Integer -> ByteString
encodeInt Integer
x, Integer -> ByteString
encodeInt Integer
y ]
                   addr :: Expr 'EWord
addr = W256 -> Expr 'EWord
Lit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word256 -> W256
W256 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word256
word256 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString -> ByteString
BS.drop Int
12 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString -> ByteString
BS.take Int
32 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
keccakBytes forall a b. (a -> b) -> a -> b
$ ByteString
pub
                in Expr 'EWord -> Maybe Addr
exprToAddr Expr 'EWord
addr
         where
          curve :: Curve
curve = CurveName -> Curve
getCurveByName CurveName
SEC_p256k1
          pubPoint :: Point
pubPoint = Curve -> Integer -> Point
generateQ Curve
curve (forall a b. (Integral a, Num b) => a -> b
num Integer
sk)
          encodeInt :: Integer -> ByteString
encodeInt = AbiValue -> ByteString
encodeAbiValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word256 -> AbiValue
AbiUInt Int
256 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger

sign :: W256 -> Integer -> (Word8, W256, W256)
sign :: W256 -> Integer -> (Word8, W256, W256)
sign W256
hash Integer
sk = (Word8
v, W256
r, W256
s)
  where
    -- setup curve params
    curve :: Curve
curve = CurveName -> Curve
getCurveByName CurveName
SEC_p256k1
    priv :: PrivateKey
priv = Curve -> Integer -> PrivateKey
PrivateKey Curve
curve Integer
sk
    digest :: Digest Keccak_256
digest = forall a. a -> Maybe a -> a
fromMaybe
      (forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Internal Error: could produce a digest from " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show W256
hash)
      (forall a ba.
(HashAlgorithm a, ByteArrayAccess ba) =>
ba -> Maybe (Digest a)
Crypto.digestFromByteString (W256 -> ByteString
word256Bytes W256
hash))

    -- sign message
    sig :: Signature
sig = PrivateKey -> Digest Keccak_256 -> Signature
ethsign PrivateKey
priv Digest Keccak_256
digest
    r :: W256
r = forall a b. (Integral a, Num b) => a -> b
num forall a b. (a -> b) -> a -> b
$ Signature -> Integer
sign_r Signature
sig
    s :: W256
s = forall a b. (Integral a, Num b) => a -> b
num Integer
lowS

    -- this is a little bit sad, but cryptonite doesn't give us back a v value
    -- so we compute it by guessing one, and then seeing if that gives us the right answer from ecrecover
    v :: Word8
v = if W256 -> W256 -> W256 -> W256 -> Maybe Addr
ecrec W256
28 W256
r W256
s W256
hash forall a. Eq a => a -> a -> Bool
== Integer -> Maybe Addr
deriveAddr Integer
sk
        then Word8
28
        else Word8
27

    -- we always use the lower S value to conform with EIP2 (re: ECDSA transaction malleability)
    -- https://eips.ethereum.org/EIPS/eip-2
    secpOrder :: Integer
secpOrder = Integer
0xfffffffffffffffffffffffffffffffebaaedce6af48a03bbfd25e8cd0364141 :: Integer
    lowS :: Integer
lowS = if Signature -> Integer
sign_s Signature
sig forall a. Ord a => a -> a -> Bool
> Integer
secpOrder forall a. Integral a => a -> a -> a
`div` Integer
2
           then Integer
secpOrder forall a. Num a => a -> a -> a
- Signature -> Integer
sign_s Signature
sig
           else Signature -> Integer
sign_s Signature
sig

-- | We don't want to introduce the machinery needed to sign with a random nonce,
-- so we just use the same nonce every time (420). This is obviously very
-- insecure, but fine for testing purposes.
ethsign :: PrivateKey -> Crypto.Digest Crypto.Keccak_256 -> Signature
ethsign :: PrivateKey -> Digest Keccak_256 -> Signature
ethsign PrivateKey
sk Digest Keccak_256
digest = Integer -> Signature
go Integer
420
  where
    go :: Integer -> Signature
go Integer
k = case forall hash.
HashAlgorithm hash =>
Integer -> PrivateKey -> Digest hash -> Maybe Signature
signDigestWith Integer
k PrivateKey
sk Digest Keccak_256
digest of
       Maybe Signature
Nothing  -> Integer -> Signature
go (Integer
k forall a. Num a => a -> a -> a
+ Integer
1)
       Just Signature
sig -> Signature
sig

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])