-- SPDX-FileCopyrightText: 2020 Tocqueville Group
--
-- SPDX-License-Identifier: LicenseRef-MIT-TQ

-- | 'TxData' type and associated functionality.

module Michelson.Runtime.TxData
       ( TxData (..)
       , tdSenderAddressL
       , tdParameterL
       , tdEntrypointL
       , tdAmountL
       ) where

import Control.Lens (makeLensesWith)
import Data.Aeson.TH (deriveJSON)

import Michelson.Untyped (EpName, Value)
import Tezos.Address (Address)
import Tezos.Core (Mutez)
import Util.Aeson (morleyAesonOptions)
import Util.Lens (postfixLFields)

-- | Data associated with a particular transaction.
data TxData = TxData
  { TxData -> Address
tdSenderAddress :: Address
  , TxData -> Value
tdParameter :: Value
  , TxData -> EpName
tdEntrypoint :: EpName
  , TxData -> Mutez
tdAmount :: Mutez
  } deriving stock (Int -> TxData -> ShowS
[TxData] -> ShowS
TxData -> String
(Int -> TxData -> ShowS)
-> (TxData -> String) -> ([TxData] -> ShowS) -> Show TxData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxData] -> ShowS
$cshowList :: [TxData] -> ShowS
show :: TxData -> String
$cshow :: TxData -> String
showsPrec :: Int -> TxData -> ShowS
$cshowsPrec :: Int -> TxData -> ShowS
Show, TxData -> TxData -> Bool
(TxData -> TxData -> Bool)
-> (TxData -> TxData -> Bool) -> Eq TxData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxData -> TxData -> Bool
$c/= :: TxData -> TxData -> Bool
== :: TxData -> TxData -> Bool
$c== :: TxData -> TxData -> Bool
Eq)

makeLensesWith postfixLFields ''TxData
deriveJSON morleyAesonOptions ''TxData