{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Polkadot.Extrinsic.SignedExtension.TransactionPayment where
import Codec.Scale (Compact, Decode,
Encode, Generic)
import qualified GHC.Generics as GHC (Generic)
import Network.Polkadot.Extrinsic.SignedExtension (SignedExtension (..))
import Network.Polkadot.Primitives (Balance)
newtype ChargeTransactionPayment = ChargeTransactionPayment (Compact Balance)
deriving (ChargeTransactionPayment -> ChargeTransactionPayment -> Bool
(ChargeTransactionPayment -> ChargeTransactionPayment -> Bool)
-> (ChargeTransactionPayment -> ChargeTransactionPayment -> Bool)
-> Eq ChargeTransactionPayment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChargeTransactionPayment -> ChargeTransactionPayment -> Bool
== :: ChargeTransactionPayment -> ChargeTransactionPayment -> Bool
$c/= :: ChargeTransactionPayment -> ChargeTransactionPayment -> Bool
/= :: ChargeTransactionPayment -> ChargeTransactionPayment -> Bool
Eq, Int -> ChargeTransactionPayment -> ShowS
[ChargeTransactionPayment] -> ShowS
ChargeTransactionPayment -> String
(Int -> ChargeTransactionPayment -> ShowS)
-> (ChargeTransactionPayment -> String)
-> ([ChargeTransactionPayment] -> ShowS)
-> Show ChargeTransactionPayment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChargeTransactionPayment -> ShowS
showsPrec :: Int -> ChargeTransactionPayment -> ShowS
$cshow :: ChargeTransactionPayment -> String
show :: ChargeTransactionPayment -> String
$cshowList :: [ChargeTransactionPayment] -> ShowS
showList :: [ChargeTransactionPayment] -> ShowS
Show, All SListI (Code ChargeTransactionPayment)
All SListI (Code ChargeTransactionPayment) =>
(ChargeTransactionPayment -> Rep ChargeTransactionPayment)
-> (Rep ChargeTransactionPayment -> ChargeTransactionPayment)
-> Generic ChargeTransactionPayment
Rep ChargeTransactionPayment -> ChargeTransactionPayment
ChargeTransactionPayment -> Rep ChargeTransactionPayment
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: ChargeTransactionPayment -> Rep ChargeTransactionPayment
from :: ChargeTransactionPayment -> Rep ChargeTransactionPayment
$cto :: Rep ChargeTransactionPayment -> ChargeTransactionPayment
to :: Rep ChargeTransactionPayment -> ChargeTransactionPayment
Generic, (forall x.
ChargeTransactionPayment -> Rep ChargeTransactionPayment x)
-> (forall x.
Rep ChargeTransactionPayment x -> ChargeTransactionPayment)
-> Generic ChargeTransactionPayment
forall x.
Rep ChargeTransactionPayment x -> ChargeTransactionPayment
forall x.
ChargeTransactionPayment -> Rep ChargeTransactionPayment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ChargeTransactionPayment -> Rep ChargeTransactionPayment x
from :: forall x.
ChargeTransactionPayment -> Rep ChargeTransactionPayment x
$cto :: forall x.
Rep ChargeTransactionPayment x -> ChargeTransactionPayment
to :: forall x.
Rep ChargeTransactionPayment x -> ChargeTransactionPayment
GHC.Generic, Putter ChargeTransactionPayment
Putter ChargeTransactionPayment -> Encode ChargeTransactionPayment
forall a. Putter a -> Encode a
$cput :: Putter ChargeTransactionPayment
put :: Putter ChargeTransactionPayment
Encode, Get ChargeTransactionPayment
Get ChargeTransactionPayment -> Decode ChargeTransactionPayment
forall a. Get a -> Decode a
$cget :: Get ChargeTransactionPayment
get :: Get ChargeTransactionPayment
Decode)
instance SignedExtension ChargeTransactionPayment where
type AdditionalSigned ChargeTransactionPayment = ()
additional_signed :: forall (m :: * -> *).
JsonRpc m =>
ChargeTransactionPayment
-> m (AdditionalSigned ChargeTransactionPayment)
additional_signed ChargeTransactionPayment
_ = () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()