~zinigor/cardano-node/trunk

« back to all changes in this revision

Viewing changes to cardano-api/src/Cardano/Api/Fees.hs

  • Committer: Igor Zinovyev
  • Date: 2021-08-13 19:12:27 UTC
  • Revision ID: zinigor@gmail.com-20210813191227-stlnsj3mc5ypwn0c
Tags: upstream-1.27.0
ImportĀ upstreamĀ versionĀ 1.27.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# LANGUAGE DataKinds #-}
 
2
{-# LANGUAGE EmptyCase #-}
 
3
{-# LANGUAGE GADTs #-}
 
4
{-# LANGUAGE ScopedTypeVariables #-}
 
5
{-# LANGUAGE TypeApplications #-}
 
6
 
 
7
-- | Fee calculation
 
8
--
 
9
module Cardano.Api.Fees (
 
10
    transactionFee,
 
11
    estimateTransactionFee,
 
12
  ) where
 
13
 
 
14
import           Prelude
 
15
 
 
16
import qualified Data.ByteString as BS
 
17
import           GHC.Records (HasField (..))
 
18
import           Numeric.Natural
 
19
 
 
20
import qualified Cardano.Binary as CBOR
 
21
import qualified Cardano.Chain.Common as Byron
 
22
 
 
23
import           Cardano.Api.Eras
 
24
import           Cardano.Api.NetworkId
 
25
import           Cardano.Api.Tx
 
26
import           Cardano.Api.Value
 
27
 
 
28
 
 
29
-- ----------------------------------------------------------------------------
 
30
-- Transaction fees
 
31
--
 
32
 
 
33
-- | For a concrete fully-constructed transaction, determine the minimum fee
 
34
-- that it needs to pay.
 
35
--
 
36
-- This function is simple, but if you are doing input selection then you
 
37
-- probably want to consider estimateTransactionFee.
 
38
--
 
39
transactionFee :: forall era.
 
40
                  IsShelleyBasedEra era
 
41
               => Natural -- ^ The fixed tx fee
 
42
               -> Natural -- ^ The tx fee per byte
 
43
               -> Tx era
 
44
               -> Lovelace
 
45
transactionFee txFeeFixed txFeePerByte (ShelleyTx _ tx) =
 
46
    Lovelace (a * x + b)
 
47
  where
 
48
    a = toInteger txFeePerByte
 
49
    x = getField @"txsize" tx
 
50
    b = toInteger txFeeFixed
 
51
 
 
52
--TODO: This can be made to work for Byron txs too. Do that: fill in this case
 
53
-- and remove the IsShelleyBasedEra constraint.
 
54
transactionFee _ _ (ByronTx _) =
 
55
    case shelleyBasedEra :: ShelleyBasedEra era of {}
 
56
 
 
57
 
 
58
--TODO: in the Byron case the per-byte is non-integral, would need different
 
59
-- parameters. e.g. a new data type for fee params, Byron vs Shelley
 
60
 
 
61
-- | This can estimate what the transaction fee will be, based on a starting
 
62
-- base transaction, plus the numbers of the additional components of the
 
63
-- transaction that may be added.
 
64
--
 
65
-- So for example with wallet coin selection, the base transaction should
 
66
-- contain all the things not subject to coin selection (such as script inputs,
 
67
-- metadata, withdrawals, certs etc)
 
68
--
 
69
estimateTransactionFee :: forall era.
 
70
                          IsShelleyBasedEra era
 
71
                       => NetworkId
 
72
                       -> Natural -- ^ The fixed tx fee
 
73
                       -> Natural -- ^ The tx fee per byte
 
74
                       -> Tx era
 
75
                       -> Int -- ^ The number of extra UTxO transaction inputs
 
76
                       -> Int -- ^ The number of extra transaction outputs
 
77
                       -> Int -- ^ The number of extra Shelley key witnesses
 
78
                       -> Int -- ^ The number of extra Byron key witnesses
 
79
                       -> Lovelace
 
80
estimateTransactionFee nw txFeeFixed txFeePerByte (ShelleyTx era tx) =
 
81
    let Lovelace baseFee = transactionFee txFeeFixed txFeePerByte (ShelleyTx era tx)
 
82
     in \nInputs nOutputs nShelleyKeyWitnesses nByronKeyWitnesses ->
 
83
 
 
84
        --TODO: this is fragile. Move something like this to the ledger and
 
85
        -- make it robust, based on the txsize calculation.
 
86
        let extraBytes :: Int
 
87
            extraBytes = nInputs               * sizeInput
 
88
                       + nOutputs              * sizeOutput
 
89
                       + nByronKeyWitnesses    * sizeByronKeyWitnesses
 
90
                       + nShelleyKeyWitnesses  * sizeShelleyKeyWitnesses
 
91
 
 
92
         in Lovelace (baseFee + toInteger txFeePerByte * toInteger extraBytes)
 
93
  where
 
94
    sizeInput               = smallArray + uint + hashObj
 
95
    sizeOutput              = smallArray + uint + address
 
96
    sizeByronKeyWitnesses   = smallArray + keyObj + sigObj + ccodeObj + attrsObj
 
97
    sizeShelleyKeyWitnesses = smallArray + keyObj + sigObj
 
98
 
 
99
    smallArray  = 1
 
100
    uint        = 5
 
101
 
 
102
    hashObj     = 2 + hashLen
 
103
    hashLen     = 32
 
104
 
 
105
    keyObj      = 2 + keyLen
 
106
    keyLen      = 32
 
107
 
 
108
    sigObj      = 2 + sigLen
 
109
    sigLen      = 64
 
110
 
 
111
    ccodeObj    = 2 + ccodeLen
 
112
    ccodeLen    = 32
 
113
 
 
114
    address     = 2 + addrHeader + 2 * addrHashLen
 
115
    addrHeader  = 1
 
116
    addrHashLen = 28
 
117
 
 
118
    attrsObj    = 2 + BS.length attributes
 
119
    attributes  = CBOR.serialize' $
 
120
                    Byron.mkAttributes Byron.AddrAttributes {
 
121
                      Byron.aaVKDerivationPath = Nothing,
 
122
                      Byron.aaNetworkMagic     = toByronNetworkMagic nw
 
123
                    }
 
124
 
 
125
--TODO: This can be made to work for Byron txs too. Do that: fill in this case
 
126
-- and remove the IsShelleyBasedEra constraint.
 
127
estimateTransactionFee _ _ _ (ByronTx _) =
 
128
    case shelleyBasedEra :: ShelleyBasedEra era of {}
 
129