Skip to content

Commit

Permalink
Use estimation rather than calculation and change to CoinSelection as…
Browse files Browse the repository at this point in the history
… arg

proper file to ingest
  • Loading branch information
paweljakubas committed Apr 25, 2019
1 parent 2cb36af commit e896902
Show file tree
Hide file tree
Showing 2 changed files with 75 additions and 88 deletions.
113 changes: 68 additions & 45 deletions src/Cardano/Wallet/CoinSelection/Fee.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,23 +27,21 @@ module Cardano.Wallet.CoinSelection.Fee

import Prelude

import Cardano.Wallet.Binary
( encodeSignedTx )
import Cardano.Wallet.CoinSelection
( CoinSelection (..) )
import Cardano.Wallet.Primitive.Types
( Coin (..)
, Tx (..)
, TxIn
, TxOut (..)
, TxWitness
, UTxO (..)
, balance'
, distance
, invariant
, isValidCoin
, pickRandom
)
import Codec.CBOR.Encoding
( encodeWord64 )
import Codec.CBOR.Write
( toLazyByteString )
import Control.Monad.Trans.Class
Expand All @@ -64,7 +62,6 @@ import GHC.Generics
import qualified Data.ByteString.Lazy as BL
import qualified Data.List as L

import Debug.Trace
{-------------------------------------------------------------------------------
Fee Adjustment
-------------------------------------------------------------------------------}
Expand Down Expand Up @@ -360,52 +357,78 @@ data TxSizeLinear = TxSizeLinear Double Double
cardanoPolicy :: TxSizeLinear
cardanoPolicy = TxSizeLinear 155381 43.946

-- | Estimate the fee for a transaction that has @ins@ inputs
-- and @length outs@ outputs. The @outs@ lists holds the coin value
-- of each output.
-- | Estimate the fee for a transaction that has @inps@ inputs
-- and @outps@ outputs as coming from coin selection.
--
-- NOTE: The average size of @Attributes AddrAttributes@ and
-- the transaction attributes @Attributes ()@ are both hard-coded
estimateCardanoFee
:: TxSizeLinear
-> (Tx, [TxWitness])
-> CoinSelection
-> Fee
estimateCardanoFee (TxSizeLinear a b) txWithWitness@(Tx inps _, _) =
trace ("totalPayload: "<> show totalPayload
<> " length : " <> show (BL.length $ toLazyByteString $ encodeSignedTx txWithWitness)) $
estimateCardanoFee (TxSizeLinear a b) (CoinSelection inps outs _) =
Fee $ ceiling $ a + b*totalPayload
where
-- The size of TxIn is always the same as it contains the hash and index
-- see Cardano.Wallet.Binary (encodeTxIn)
sizeOfTxIn :: Int
sizeOfTxIn = 42

sizeOfListLen :: Int
sizeOfListLen = 1

sizeOfListBreak :: Int
sizeOfListBreak = 1

-- The size of [TxIn]
sizeOfTxIns :: Int
sizeOfTxIns =
let n = length inps
in sizeOfListLen + n*sizeOfTxIn + (n-1)*sizeOfListBreak + (n-1)*2

-- The size of TxWitness is always the same as it contains data constructor and hash
-- see Cardano.Wallet.Binary (encodeTxWitness)
sizeOfTxWitness :: Int
sizeOfTxWitness = 139

-- The size of [TxWitness]
sizeOfTxWitnesses :: Int
sizeOfTxWitnesses =
let n = length inps
in sizeOfListLen + n*sizeOfTxWitness + (n-1)*sizeOfListBreak

-- The size of TxOut depends only on the coin value
-- see Cardano.Wallet.Binary (encodeTxOut)
sizeOfTxOut :: Word64 -> Int
sizeOfTxOut =
(+77) . fromIntegral . BL.length . toLazyByteString . encodeWord64

-- The size of [TxOut]
sizeOfTxOuts :: Int
sizeOfTxOuts =
let n = length outs
coins = map (getCoin . coin) outs
in sizeOfListLen + sum (map sizeOfTxOut coins) + (n-1)*sizeOfListBreak


-- The size of [[TxIn], [TxWitness]]
sizeOfTx :: Int
sizeOfTx =
sizeOfListLen + sizeOfTxWitnesses + sizeOfTxIns + sizeOfTxOuts + 2*sizeOfListBreak


totalPayload :: Double
totalPayload = fromIntegral
$ boundAddrAttrSize + boundTxAttrSize + boundSignatureWitnessSize + payloadFromTxWithWitness + 4*(length inps - 1)

payloadFromTxWithWitness :: Int
payloadFromTxWithWitness = (fromIntegral . BL.length . toLazyByteString . encodeSignedTx) txWithWitness

-- | Size to use for a value of type @Attributes AddrAttributes@ when estimating
-- encoded transaction sizes. The minimum possible value is 2.
--
-- NOTE: When the /actual/ size exceeds this bounds, we may underestimate
-- tranasction fees and potentially generate invalid transactions.
--
-- `boundAddrAttrSize` needed to increase due to the inclusion of
-- `NetworkMagic` in `AddrAttributes`. The `Bi` instance of
-- `AddrAttributes` serializes `NetworkTestnet` as [(Word8,Int32)] and
-- `NetworkMainOrStage` as []; this should require a 5 Byte increase in
--`boundAddrAttrSize`. Because encoding in unit tests is not guaranteed
-- to be efficient, it was decided to increase by 7 Bytes to mitigate
-- against potential random test failures in the future.
boundAddrAttrSize :: Int
boundAddrAttrSize = 34 + 7 -- 7 bytes for potential NetworkMagic

-- | Size to use for a value of type @Attributes ()@ when estimating
-- encoded transaction sizes. The minimum possible value is 2.
--
-- NOTE: When the /actual/ size exceeds this bounds, we may underestimate
-- transaction fees and potentially generate invalid transactions.
boundTxAttrSize :: Int
boundTxAttrSize = 2

-- | Signature of witness payload
boundSignatureWitnessSize :: Int
boundSignatureWitnessSize = 66
totalPayload = fromIntegral $
sizeOfListLen + sizeOfListBreak + sizeOfTx + sizeOfAddrAttr + sizeOfTxAttr + sizeOfSignatureWitness

-- taken from cardano-sl
sizeOfAddrAttr :: Int
sizeOfAddrAttr = 34 + 7

-- taken from cardano-sl
sizeOfTxAttr :: Int
sizeOfTxAttr = 2

-- taken from cardano-sl
sizeOfSignatureWitness :: Int
sizeOfSignatureWitness = 66
50 changes: 7 additions & 43 deletions test/unit/Cardano/Wallet/CoinSelection/FeeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,17 +25,7 @@ import Cardano.Wallet.CoinSelection.Policy.LargestFirst
import Cardano.Wallet.CoinSelectionSpec
( CoinSelProp (..), genTxOut, genUTxO )
import Cardano.Wallet.Primitive.Types
( Address (..)
, Coin (..)
, Hash (..)
, ShowFmt (..)
, Tx (..)
, TxIn (..)
, TxOut (..)
, TxOut (..)
, TxWitness (..)
, UTxO (..)
)
( Coin (..), ShowFmt (..), TxOut (..), UTxO (..) )
import Control.Arrow
( left )
import Control.Monad
Expand All @@ -46,12 +36,6 @@ import Crypto.Random
( SystemDRG, getSystemDRG )
import Crypto.Random.Types
( withDRG )
import Data.ByteArray.Encoding
( Base (Base16), convertFromBase )
import Data.ByteString
( ByteString )
import Data.ByteString.Base58
( bitcoinAlphabet, decodeBase58 )
import Data.Char
( ord )
import Data.Csv
Expand Down Expand Up @@ -90,8 +74,6 @@ import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Vector as V

import Debug.Trace

spec :: Spec
spec = do
describe "Fee calculation : unit tests" $ do
Expand Down Expand Up @@ -389,30 +371,12 @@ realisticFeeUnitTest = it "realistic fee calculations" $ do
let sum' = sum $ L.tail $ L.sort inps
in (sum' < (fee + sum outs))
checkFee :: FeeCase -> Expectation
checkFee (FeeCase inps outs fee) = do
let txIns = zipWith TxIn (replicate (length inps) inputId0) [0..]
let txOuts = zipWith TxOut (replicate (length outs) address0) (map Coin outs)
let tx = Tx txIns txOuts
let (Fee estFee) = estimateCardanoFee cardanoPolicy (tx, replicate (length inps) (PublicKeyWitness pkWitness))
trace ("estFee "<>show estFee) $ estFee `shouldBe` fee
inputId0 = hash16
"60dbb2679ee920540c18195a3d92ee9be50aee6ed5f891d92d51db8a76b02cd2"
address0 = addr58
"DdzFFzCqrhsug8jKBMV5Cr94hKY4DrbJtkUpqptoGEkovR2QSkcA\
\cRgjnUyegE689qBX6b2kyxyNvCL6mfqiarzRB9TRq8zwJphR31pr"
pkWitness = "\130X@\226E\220\252\DLE\170\216\210\164\155\182mm$ePG\252\186\195\225_\b=\v\241=\255 \208\147[\239\RS\170|\214\202\247\169\229\205\187O_)\221\175\155?e\198\248\170\157-K\155\169z\144\174\ENQhX@\193\151*,\NULz\205\234\&1tL@\211\&2\165\129S\STXP\164C\176 Xvf\160|;\CANs{\SYN\204<N\207\154\130\225\229\t\172mbC\139\US\159\246\168x\163Mq\248\145)\160|\139\207-\SI"

-- | Make a Hash from a Base16 encoded string, without error handling.
hash16 :: ByteString -> Hash a
hash16 = either bomb Hash . convertFromBase Base16
where
bomb msg = error ("Could not decode test string: " <> msg)

-- | Make an Address from a Base58 encoded string, without error handling.
addr58 :: ByteString -> Address
addr58 = maybe (error "addr58: Could not decode") Address
. decodeBase58 bitcoinAlphabet

checkFee (FeeCase inps' outs' fee) = do
inps <- (Map.toList . getUTxO) <$> generate (genUTxO inps')
outs <- generate (genTxOut outs')
let coinSel = CoinSelection inps outs []
let (Fee estFee) = estimateCardanoFee cardanoPolicy coinSel
estFee `shouldBe` fee

data FeeCase = FeeCase
{ csvInputs :: [Word64]
Expand Down

0 comments on commit e896902

Please sign in to comment.