{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Ethereum.Web3.Types where
import Data.Aeson
import Data.Aeson.TH
import Data.Default
import Data.Monoid ((<>))
import Data.Ord (Down (..))
import Data.String (IsString (..))
import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as B
import qualified Data.Text.Lazy.Builder.Int as B
import qualified Data.Text.Read as R
import GHC.Generics (Generic)
import Data.String.Extra (toLowerFirst)
import Network.Ethereum.ABI.Prim.Address (Address)
import Network.Ethereum.ABI.Prim.Bytes (Bytes)
import Network.Ethereum.Unit
newtype Quantity = Quantity { unQuantity :: Integer }
deriving (Show, Read, Num, Real, Enum, Eq, Ord, Generic)
instance IsString Quantity where
fromString ('0' : 'x' : hex) =
case R.hexadecimal (T.pack hex) of
Right (x, "") -> Quantity x
_ -> error "Unable to parse Quantity!"
fromString str =
case R.decimal (T.pack str) of
Right (x, "") -> Quantity x
_ -> error "Unable to parse Quantity!"
instance ToJSON Quantity where
toJSON (Quantity x) =
let hexValue = B.toLazyText (B.hexadecimal x)
in toJSON ("0x" <> hexValue)
instance FromJSON Quantity where
parseJSON (String v) =
case R.hexadecimal v of
Right (x, "") -> return (Quantity x)
_ -> fail "Unable to parse Quantity"
parseJSON _ = fail "Quantity may only be parsed from a JSON String"
instance Fractional Quantity where
(/) a b = Quantity $ div (unQuantity a) (unQuantity b)
fromRational = Quantity . floor
instance Unit Quantity where
fromWei = Quantity
toWei = unQuantity
instance UnitSpec Quantity where
divider = const 1
name = const "quantity"
newtype BlockNumber = BlockNumber Integer deriving (Eq, Show, Generic, Ord, Read, Num)
instance FromJSON BlockNumber where
parseJSON (String v) =
case R.hexadecimal v of
Right (x, "") -> return (BlockNumber x)
_ -> fail "Unable to parse BlockNumber!"
parseJSON _ = fail "The string is required!"
instance ToJSON BlockNumber where
toJSON (BlockNumber x) =
let hexValue = B.toLazyText (B.hexadecimal x)
in toJSON ("0x" <> hexValue)
data SyncActive = SyncActive { syncStartingBlock :: BlockNumber
, syncCurrentBlock :: BlockNumber
, syncHighestBlock :: BlockNumber
} deriving (Eq, Generic, Show)
$(deriveJSON (defaultOptions { fieldLabelModifier = toLowerFirst . drop 4 }) ''SyncActive)
data SyncingState = Syncing SyncActive | NotSyncing deriving (Eq, Generic, Show)
instance FromJSON SyncingState where
parseJSON (Bool _) = pure NotSyncing
parseJSON v = Syncing <$> parseJSON v
newtype FilterId = FilterId Integer
deriving (Show, Eq, Ord, Generic)
instance FromJSON FilterId where
parseJSON (String v) =
case R.hexadecimal v of
Right (x, "") -> return (FilterId x)
_ -> fail "Unable to parse FilterId!"
parseJSON _ = fail "The string is required!"
instance ToJSON FilterId where
toJSON (FilterId x) =
let hexValue = B.toLazyText (B.hexadecimal x)
in toJSON ("0x" <> hexValue)
data Change = Change
{ changeLogIndex :: !Quantity
, changeTransactionIndex :: !Quantity
, changeTransactionHash :: !Bytes
, changeBlockHash :: !Bytes
, changeBlockNumber :: !BlockNumber
, changeAddress :: !Address
, changeData :: !Bytes
, changeTopics :: ![Bytes]
} deriving (Show, Generic)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = toLowerFirst . drop 6 }) ''Change)
data Call = Call
{ callFrom :: !(Maybe Address)
, callTo :: !(Maybe Address)
, callGas :: !(Maybe Quantity)
, callGasPrice :: !(Maybe Quantity)
, callValue :: !(Maybe Quantity)
, callData :: !(Maybe Bytes)
} deriving (Show, Generic)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = toLowerFirst . drop 4
, omitNothingFields = True }) ''Call)
instance Default Call where
def = Call Nothing Nothing (Just 3000000) Nothing (Just 0) Nothing
data DefaultBlock = BlockWithNumber BlockNumber | Earliest | Latest | Pending
deriving (Show, Eq)
instance ToJSON DefaultBlock where
toJSON (BlockWithNumber bn) = toJSON bn
toJSON parameter = toJSON . toLowerFirst . show $ parameter
data Filter e = Filter
{ filterAddress :: !(Maybe Address)
, filterTopics :: !(Maybe [Maybe Bytes])
, filterFromBlock :: !DefaultBlock
, filterToBlock :: !DefaultBlock
} deriving (Show, Generic)
instance ToJSON (Filter e) where
toJSON f = object [ "address" .= filterAddress f
, "topics" .= filterTopics f
, "fromBlock" .= filterFromBlock f
, "toBlock" .= filterToBlock f
]
instance Ord DefaultBlock where
compare Pending Pending = EQ
compare Latest Latest = EQ
compare Earliest Earliest = EQ
compare (BlockWithNumber a) (BlockWithNumber b) = compare a b
compare _ Pending = LT
compare Pending Latest = GT
compare _ Latest = LT
compare Earliest _ = LT
compare a b = compare (Down b) (Down a)
data Transaction = Transaction
{ txHash :: !Bytes
, txNonce :: !Quantity
, txBlockHash :: !Bytes
, txBlockNumber :: !BlockNumber
, txTransactionIndex :: !Quantity
, txFrom :: !Address
, txTo :: !(Maybe Address)
, txValue :: !Quantity
, txGasPrice :: !Quantity
, txGas :: !Quantity
, txInput :: !Bytes
} deriving (Show, Generic)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = toLowerFirst . drop 2 }) ''Transaction)
data Block = Block
{ blockNumber :: !BlockNumber
, blockHash :: !Bytes
, blockParentHash :: !Bytes
, blockNonce :: !(Maybe Bytes)
, blockSha3Uncles :: !Bytes
, blockLogsBloom :: !Bytes
, blockTransactionsRoot :: !Bytes
, blockStateRoot :: !Bytes
, blockReceiptRoot :: !(Maybe Bytes)
, blockMiner :: !Address
, blockDifficulty :: !Quantity
, blockTotalDifficulty :: !Quantity
, blockExtraData :: !Bytes
, blockSize :: !Quantity
, blockGasLimit :: !Quantity
, blockGasUsed :: !Quantity
, blockTimestamp :: !Quantity
, blockTransactions :: ![Transaction]
, blockUncles :: ![Bytes]
} deriving (Show, Generic)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = toLowerFirst . drop 5 }) ''Block)
type TxHash = Bytes