Skip to content

Commit

Permalink
tmp
Browse files Browse the repository at this point in the history
  • Loading branch information
polinavino committed Jan 19, 2021
1 parent ad1d7b5 commit bef4525
Show file tree
Hide file tree
Showing 5 changed files with 98 additions and 114 deletions.
79 changes: 23 additions & 56 deletions shelley-ma/impl/src/Cardano/Ledger/Mary/Value.hs
Expand Up @@ -156,70 +156,37 @@ instance CC.Crypto crypto => Val (Value crypto) where
modifyCoin f (Value c m) = Value n m where (Coin n) = f (Coin c)
pointwise p (Value c x) (Value d y) = (p c d) && (pointWise (pointWise p) x y)

{- Explanation of the Value size calculation :
The size calculation is to approximate the number of bytes in a
compact representation of Value (CompactValue). CompactValue has two constructors :
1. CompactValueAdaOnly is used when v == mempty
it takes a Word64 to represent an ada amount (unpacked in the compact representation)
2. CompactValueMultiAsset (used otherwise) takes an ada amount and token bundle data
i) Word64 (ada)
ii) Word (number of distinct types of multi-assets in the bundle)
iii) rep :
The rep consists of five parts
A) a sequence of Word64s representing quantities
B) a sequence of Word16s representing policyId indices
C) Word16s representing asset name indices
(as a special case for empty asset names,
the index points to the end of the string)
D) a blob of policyIDs
E) a blob of asset names
-}

-- returns the size, in Word64's, of the CompactValue representation of Value
size (Value _ v)
-- based on size in words stored in the compact representation of Value
| v == mempty = fromIntegral $ adaWords * wordLength
| otherwise =
fromIntegral $ wordLength * (adaWords + noMAs) + repSize
where
repSize =
wordLength * quanSize * totalNoAssets
+ 2 * totalNoAssets * (index * wordLength)
+ pidLength * noPIDs
+ assetNamesLength
where
noPIDs = length $ Map.keys v
allAssets :: [AssetName]
allAssets = (Map.foldr (\a b -> (Map.keys a) ++ b) [] v)
totalNoAssets = length allAssets
assetNames = LS.nub $ LS.sort allAssets
assetNamesLength = LS.foldr (\(AssetName a) b -> (BS.length a) + b) 0 assetNames

-- 64 bit machine word length
wordLength :: Int
wordLength = 8

-- ada is represented by 2 words
-- when Value contains only ada
| v == mempty = fromIntegral $ adaWords
-- when Value contains ada as well as other tokens
-- sums up :
-- i) adaWords : the space taken up by the ada amount
-- ii) noMAs : the space taken by number of words used to store number of non-ada assets in a value
-- iii) the space taken up by the rest of the representation (quantities, PIDs, AssetNames, indeces)
-- these are all unpacked, so there is no extra overhead
| otherwise = fromIntegral $ adaWords + noMAs + (roundupBytesToWords $ repSize v)

-- TODO temp repSize
repSize :: Map (PolicyID crypto) (Map AssetName Integer) -> Int
repSize = 0

-- space (in Word64s) taken up by the ada amount
adaWords :: Int
adaWords = 2
adaWords = 1

-- number of words used to represent quantity
quanSize :: Int
quanSize = 1

-- number of bytes to represent index
index :: Int
index = 2
-- 64 bit machine Word64 length
wordLength :: Int
wordLength = 8

-- number of words used to store number of MAs in a value
noMAs :: Int
noMAs = 1

-- length of PID in bytes
pidLength :: Int
pidLength = 28
-- converts bytes to words (rounding up)
roundupBytesToWords :: Int -> Int
roundupBytesToWords b = ceiling $ (b + (wordLength - 1)) / wordLength

-- ==============================================================
-- CBOR
Expand Down
58 changes: 58 additions & 0 deletions shelley-ma/impl/src/Cardano/Ledger/ShelleyMA/Rules/Utxo.hs
Expand Up @@ -86,6 +86,64 @@ import Shelley.Spec.Ledger.UTxO

-- ==========================================================


{- The scaledMinDeposit calculation uses the minUTxOValue protocol parameter
(passed to it as Coin mv) as a specification of "the cost of
making a Shelley-sized UTxO entry", calculated here by "utxoEntrySizeWithoutVal + uint",
using the constants in the "where" clause.
In the case when a UTxO entry contains coins only (and the Shelley
UTxO entry format is used - we will extend this to be correct for other
UTxO formats shortly), the deposit should be exactly the minUTxOValue.
This is the "inject (coin v) == v" case.
Otherwise, we calculate the per-byte deposit by multiplying the minimum deposit (which is
for the number of Shelley UTxO-entry bytes) by the size of a Shelley UTxO entry.
This is the "(mv * (utxoEntrySizeWithoutVal + uint))" calculation.
We then calculate the total deposit required for making a UTxO entry with a Val-class
member v by dividing "(mv * (utxoEntrySizeWithoutVal + uint))" by the
estimated total size of the UTxO entry containing v, ie by
"(utxoEntrySizeWithoutVal + size v)".
See the formal specification for details.
-}

-- This scaling function is right for UTxO, not EUTxO
--
scaledMinDeposit :: (Val v) => v -> Coin -> Coin
scaledMinDeposit v (Coin mv)
| inject (coin v) == v = Coin mv -- without non-Coin assets, scaled deposit should be exactly minUTxOValue
-- The calculation should represent this equation
-- minValueParameter / coinUTxOSize = actualMinValue / valueUTxOSize
-- actualMinValue = (minValueParameter / coinUTxOSize) * valueUTxOSize
| otherwise = Coin $ max mv (adaPerUTxOByte * (utxoEntrySizeWithoutVal + size v))
where
-- lengths obtained from tracing on HeapWords of inputs and outputs
txoutLen :: Integer
txoutLen = 14

txinLen :: Integer
txinLen = 7

-- unpacked CompactCoin Word64 size in words
coinSize :: Integer
coinSize = fromIntegral $ heapWordsUnpacked (CompactCoin 0)

-- bytes in a word
wordSize :: Integer
wordSize = 8

utxoEntrySizeWithoutVal :: Integer
utxoEntrySizeWithoutVal = (6 + txoutLen + txinLen) * wordSize

-- how much ada does a byte of UTxO space cost, calculated from minAdaValue PP
-- round down
adaPerUTxOByte :: Integer
adaPerUTxOByte = quot mv (utxoEntrySizeWithoutVal + coinSize * wordSize)


data UtxoPredicateFailure era
= BadInputsUTxO
!(Set (TxIn (Crypto era))) -- The bad transaction inputs
Expand Down
56 changes: 0 additions & 56 deletions shelley/chain-and-ledger/executable-spec/src/Cardano/Ledger/Val.hs
Expand Up @@ -102,62 +102,6 @@ instance Val Coin where

deriving via Coin instance Val DeltaCoin

{- The scaledMinDeposit calculation uses the minUTxOValue protocol parameter
(passed to it as Coin mv) as a specification of "the cost of
making a Shelley-sized UTxO entry", calculated here by "utxoEntrySizeWithoutVal + uint",
using the constants in the "where" clause.
In the case when a UTxO entry contains coins only (and the Shelley
UTxO entry format is used - we will extend this to be correct for other
UTxO formats shortly), the deposit should be exactly the minUTxOValue.
This is the "inject (coin v) == v" case.
Otherwise, we calculate the per-byte deposit by multiplying the minimum deposit (which is
for the number of Shelley UTxO-entry bytes) by the size of a Shelley UTxO entry.
This is the "(mv * (utxoEntrySizeWithoutVal + uint))" calculation.
We then calculate the total deposit required for making a UTxO entry with a Val-class
member v by dividing "(mv * (utxoEntrySizeWithoutVal + uint))" by the
estimated total size of the UTxO entry containing v, ie by
"(utxoEntrySizeWithoutVal + size v)".
See the formal specification for details.
-}

-- TODO : This scaling function is right for UTxO, not EUTxO
-- constants are temporary, the UTxO entry size calculation will be moved
scaledMinDeposit :: (Val v) => v -> Coin -> Coin
scaledMinDeposit v (Coin mv)
| inject (coin v) == v = Coin mv -- without non-Coin assets, scaled deposit should be exactly minUTxOValue
-- The calculation should represent this equation
-- minValueParameter / coinUTxOSize = actualMinValue / valueUTxOSize
-- actualMinValue = (minValueParameter / coinUTxOSize) * valueUTxOSize
| otherwise = Coin $ adaPerUTxOByte * (utxoEntrySizeWithoutVal + size v)
where
-- lengths obtained from tracing on HeapWords of inputs and outputs, plus 6 for Map overhead
txoutLen :: Integer
txoutLen = 14

txinLen :: Integer
txinLen = 7

-- unpacked CompactCoin Word64 size in words
coinSize :: Integer
coinSize = fromIntegral $ heapWordsUnpacked (Coin 0)

-- bytes in a word
wordSize :: Integer
wordSize = 8

utxoEntrySizeWithoutVal :: Integer
utxoEntrySizeWithoutVal = (6 + txoutLen + txinLen) * wordSize

-- how much ada does a byte of UTxO space cost, calculated from minAdaValue PP
-- round down
adaPerUTxOByte :: Integer
adaPerUTxOByte = quot mv (utxoEntrySizeWithoutVal + coinSize * wordSize)

-- =============================================================

class DecodeNonNegative v where
Expand Down
Expand Up @@ -392,7 +392,7 @@ utxoInductive = do
filter
( \x ->
let c = getField @"value" x
in (Val.coin c) < (Val.scaledMinDeposit c minUTxOValue)
in (Val.coin c) < minUTxOValue
)
outputs
null outputsTooSmall ?! OutputTooSmallUTxO outputsTooSmall
Expand Down
Expand Up @@ -116,6 +116,7 @@ import Data.Coders
field,
(!>),
)
import qualified Cardano.Prelude as HW
import Data.Coerce (coerce)
import Data.Constraint (Constraint)
import Data.Foldable (asum)
Expand Down Expand Up @@ -417,14 +418,19 @@ instance CC.Crypto crypto => FromJSON (PoolParams crypto) where
-- | A unique ID of a transaction, which is computable from the transaction.
newtype TxId crypto = TxId {_unTxId :: Hash crypto EraIndependentTxBody}
deriving (Show, Eq, Ord, Generic)
deriving newtype (NoThunks)
deriving newtype (NoThunks, HeapWords)

deriving newtype instance HeapWords (HS.Hash h a)

deriving newtype instance CC.Crypto crypto => ToCBOR (TxId crypto)

deriving newtype instance CC.Crypto crypto => FromCBOR (TxId crypto)

deriving newtype instance CC.Crypto crypto => NFData (TxId crypto)

instance HeapWords (TxIn crypto) where
heapWords (TxInCompact txid ix) = 3 + HW.heapWordsUnpacked txid + HW.heapWordsUnpacked (ix)

type TransTxId (c :: Type -> Constraint) era =
-- Transaction Ids are the hash of a transaction body, which contains
-- a Core.TxBody and Core.TxOut, hence the need for the ToCBOR instances
Expand Down Expand Up @@ -476,6 +482,15 @@ type TransTxOut (c :: Type -> Constraint) era =
Compactible (Core.Value era)
)

instance HeapWords (TxOut era) where
heapWords (TxOutCompact a vl) = 3 + HW.heapWordsUnpacked packed57Bytestring + size vl

-- the length of a shelley base address estimate (stake and payment are 28-long)
-- TODO do we want a different estimate here instead?
-- use real crypto
packed57Bytestring :: ByteString
packed57Bytestring = Char8.pack (replicate 57 'a')

instance
(TransTxOut Show era, Era era) => -- Use the weakest constraint possible here
Show (TxOut era)
Expand Down

0 comments on commit bef4525

Please sign in to comment.