{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Ethereum.Api.Personal where
import Data.ByteArray.HexString (HexString)
import Data.Solidity.Prim.Address (Address)
import Data.Text (Text)
import Network.Ethereum.Api.Types (Call)
import Network.JsonRpc.TinyClient (JsonRpc (..))
type Passphrase = Text
importRawKey :: JsonRpc m => HexString -> Passphrase -> m Address
{-# INLINE importRawKey #-}
importRawKey :: HexString -> Passphrase -> m Address
importRawKey = Passphrase -> HexString -> Passphrase -> m Address
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_importRawKey"
listAccounts :: JsonRpc m => m [Address]
{-# INLINE listAccounts #-}
listAccounts :: m [Address]
listAccounts = Passphrase -> m [Address]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_listAccounts"
lockAccount :: JsonRpc m => Address -> m Bool
{-# INLINE lockAccount #-}
lockAccount :: Address -> m Bool
lockAccount = Passphrase -> Address -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_lockAccount"
newAccount :: JsonRpc m => Passphrase -> m Address
{-# INLINE newAccount #-}
newAccount :: Passphrase -> m Address
newAccount = Passphrase -> Passphrase -> m Address
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_newAccount"
unlockAccount :: JsonRpc m => Address -> Passphrase -> m Bool
{-# INLINE unlockAccount #-}
unlockAccount :: Address -> Passphrase -> m Bool
unlockAccount = Passphrase -> Address -> Passphrase -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_unlockAccount"
sendTransaction :: JsonRpc m => Call -> Passphrase -> m HexString
{-# INLINE sendTransaction #-}
sendTransaction :: Call -> Passphrase -> m HexString
sendTransaction = Passphrase -> Call -> Passphrase -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_sendTransaction"
sign :: JsonRpc m => HexString -> Address -> Passphrase -> m HexString
{-# INLINE sign #-}
sign :: HexString -> Address -> Passphrase -> m HexString
sign = Passphrase -> HexString -> Address -> Passphrase -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_sign"
ecRecover :: JsonRpc m => HexString -> HexString -> m Address
{-# INLINE ecRecover #-}
ecRecover :: HexString -> HexString -> m Address
ecRecover = Passphrase -> HexString -> HexString -> m Address
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Passphrase -> a
remote Passphrase
"personal_ecRecover"