module Network.Ethereum.Web3.Types where
import           Control.Exception              (Exception)
import           Control.Monad.IO.Class         (MonadIO)
import           Data.Aeson
import           Data.Aeson.TH
import           Data.Monoid                    ((<>))
import           Data.Text                      (Text)
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           Data.Typeable                  (Typeable)
import           GHC.Generics
import           Network.Ethereum.Web3.Address  (Address)
import           Network.Ethereum.Web3.Internal (toLowerFirst)
newtype Web3 a b = Web3 { unWeb3 :: IO b }
  deriving (Functor, Applicative, Monad, MonadIO)
data Web3Error
  = JsonRpcFail !RpcError
  
  | ParserFail  !String
  
  | UserFail    !String
  
  deriving (Typeable, Show, Eq, Generic)
instance Exception Web3Error
data RpcError = RpcError
  { errCode    :: !Int
  , errMessage :: !Text
  , errData    :: !(Maybe Value)
  } deriving (Show, Eq, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 3 }) ''RpcError)
data Filter = Filter
  { filterAddress   :: !(Maybe Address)
  , filterTopics    :: !(Maybe [Maybe Text])
  , filterFromBlock :: !(Maybe Text)
  , filterToBlock   :: !(Maybe Text)
  } deriving (Show, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 6 }) ''Filter)
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         :: !Text
  , changeTransactionIndex :: !Text
  , changeTransactionHash  :: !Text
  , changeBlockHash        :: !Text
  , changeBlockNumber      :: !Text
  , changeAddress          :: !Address
  , changeData             :: !Text
  , changeTopics           :: ![Text]
  } deriving (Show, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 6 }) ''Change)
data Call = Call
  { callFrom     :: !(Maybe Address)
  , callTo       :: !Address
  , callGas      :: !(Maybe Text)
  , callGasPrice:: !(Maybe Text)
  , callValue    :: !(Maybe Text)
  , callData     :: !(Maybe Text)
  } deriving (Show, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 4
    , omitNothingFields = True }) ''Call)
data DefaultBlock = BlockNumberHex Text | Earliest | Latest | Pending
  deriving (Show, Eq)
instance ToJSON DefaultBlock where
    toJSON (BlockNumberHex hex) = toJSON hex
    toJSON parameter            = toJSON . toLowerFirst . show $ parameter
type TxHash = Text
data Transaction = Transaction
  { txHash             :: !TxHash
  
  , txNonce            :: !Text
  
  , txBlockHash        :: !Text
  
  , txBlockNumber      :: !Text
  
  , txTransactionIndex :: !Text
  
  , txFrom             :: !Address
  
  , txTo               :: !(Maybe Address)
  
  , txValue            :: !Text
  
  , txGasPrice         :: !Text
  
  , txGas              :: !Text
  
  , txInput            :: !Text
  
  } deriving (Show, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 2 }) ''Transaction)
data Block = Block
  { blockNumber           :: !Text
  
  , blockHash             :: !Text
  
  , blockParentHash       :: !Text
  
  , blockNonce            :: !(Maybe Text)
  
  , blockSha3Uncles       :: !Text
  
  , blockLogsBloom        :: !Text
  
  , blockTransactionsRoot :: !Text
  
  , blockStateRoot        :: !Text
  
  , blockReceiptRoot      :: !(Maybe Text)
  
  , blockMiner            :: !Address
  
  , blockDifficulty       :: !Text
  
  , blockTotalDifficulty  :: !Text
  
  , blockExtraData        :: !Text
  
  , blockSize             :: !Text
  
  , blockGasLimit         :: !Text
  
  , blockGasUsed          :: !Text
  
  , blockTimestamp        :: !Text
  
  , blockTransactions     :: ![Transaction]
  
  , blockUncles           :: ![Text]
  
  } deriving (Show, Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = toLowerFirst . drop 5 }) ''Block)