Skip to content

Commit

Permalink
Switch TxIx and CertIx to Word16
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Jan 10, 2025
1 parent 7573580 commit 622bde1
Show file tree
Hide file tree
Showing 6 changed files with 20 additions and 41 deletions.
4 changes: 2 additions & 2 deletions eras/babbage/impl/src/Cardano/Ledger/Babbage/Collateral.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Cardano.Ledger.UTxO (UTxO (..), coinBalance)
import Cardano.Ledger.Val ((<->))
import qualified Data.Map.Strict as Map
import Data.Maybe.Strict (StrictMaybe (..))
import Data.Word (Word16, Word64)
import Data.Word (Word16)
import Lens.Micro

-- ============================================================
Expand Down Expand Up @@ -54,4 +54,4 @@ collOuts txBody =
-- In the impossible event that there are more transaction outputs
-- in the transaction than will fit into a Word16 (which backs the TxIx),
-- we give the collateral return output an index of maxBound.
Nothing -> TxIx ((fromIntegral :: Word16 -> Word64) (maxBound :: Word16))
Nothing -> TxIx (maxBound :: Word16)
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ import Cardano.Ledger.Val (zero, (<->))
import qualified Data.ByteString.Short as SBS
import Data.Default (def)
import qualified Data.Map.Strict as Map
import Data.Word
import GHC.Stack (HasCallStack)
import Lens.Micro ((&), (.~), (^.))
import Lens.Micro.Extras (view)
Expand Down Expand Up @@ -73,7 +72,7 @@ translateCompactTxInByronToShelley ::
translateCompactTxInByronToShelley (Byron.CompactTxInUtxo compactTxId idx) =
TxIn
(translateTxIdByronToShelley (Byron.fromCompactTxId compactTxId))
(TxIx ((fromIntegral :: Word16 -> Word64) idx))
(TxIx idx)

translateUTxOByronToShelley ::
Byron.UTxO ->
Expand Down
12 changes: 6 additions & 6 deletions libs/cardano-ledger-core/src/Cardano/Ledger/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -315,8 +315,8 @@ isBootstrapRedeemer _ = False
putPtr :: Ptr -> Put
putPtr (Ptr (SlotNo slot) (TxIx txIx) (CertIx certIx)) = do
putVariableLengthWord64 slot
putVariableLengthWord64 txIx
putVariableLengthWord64 certIx
putVariableLengthWord64 (fromIntegral txIx) -- TODO: switch to using MemPack for compacting Address at which point
putVariableLengthWord64 (fromIntegral certIx) -- this conversion from Word16 to Word64 will no longer be necessary

newtype Word7 = Word7 Word8
deriving (Eq, Show)
Expand Down Expand Up @@ -721,8 +721,8 @@ decodePtr ::
decodePtr buf =
Ptr
<$> (SlotNo . (fromIntegral :: Word32 -> Word64) <$> decodeVariableLengthWord32 "SlotNo" buf)
<*> (TxIx . (fromIntegral :: Word16 -> Word64) <$> decodeVariableLengthWord16 "TxIx" buf)
<*> (CertIx . (fromIntegral :: Word16 -> Word64) <$> decodeVariableLengthWord16 "CertIx" buf)
<*> (TxIx <$> decodeVariableLengthWord16 "TxIx" buf)
<*> (CertIx <$> decodeVariableLengthWord16 "CertIx" buf)
{-# INLINE decodePtr #-}

decodePtrLenient ::
Expand All @@ -732,8 +732,8 @@ decodePtrLenient ::
decodePtrLenient buf =
Ptr
<$> (SlotNo <$> decodeVariableLengthWord64 "SlotNo" buf)
<*> (TxIx <$> decodeVariableLengthWord64 "TxIx" buf)
<*> (CertIx <$> decodeVariableLengthWord64 "CertIx" buf)
<*> (TxIx <$> decodeVariableLengthWord16 "TxIx" buf)
<*> (CertIx <$> decodeVariableLengthWord16 "CertIx" buf)
{-# INLINE decodePtrLenient #-}

guardLength ::
Expand Down
36 changes: 8 additions & 28 deletions libs/cardano-ledger-core/src/Cardano/Ledger/BaseTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -806,28 +806,15 @@ newtype BlocksMade = BlocksMade
deriving (Show) via Quiet BlocksMade
deriving newtype (NoThunks, NFData, ToJSON, FromJSON, EncCBOR, DecCBOR)

-- TODO: It is unfeasable to have 65535 outputs in a transaction,
-- but 255 is right on the border of a maximum TxIx on Mainnet at the moment,
-- that is why `Word16` was chosen as the smallest upper bound. Use
-- `txIxFromIntegral` in order to construct this index safely from anything
-- other than `Word16`. There is also `mkTxIxPartial` that can be used for
-- testing.

-- | Transaction index.
newtype TxIx = TxIx {unTxIx :: Word64}
newtype TxIx = TxIx {unTxIx :: Word16}
deriving stock (Eq, Ord, Show, Generic)
deriving newtype (NFData, Enum, Bounded, NoThunks, FromCBOR, ToCBOR, EncCBOR, ToJSON)

instance DecCBOR TxIx where
decCBOR =
ifDecoderVersionAtLeast
(natVersion @9)
(TxIx . fromIntegral @Word16 @Word64 <$> decCBOR)
(TxIx <$> decCBOR)
deriving newtype (NFData, Enum, Bounded, NoThunks, FromCBOR, ToCBOR, EncCBOR, DecCBOR, ToJSON)

-- | Construct a `TxIx` from a 16 bit unsigned integer
mkTxIx :: Word16 -> TxIx
mkTxIx = TxIx . fromIntegral
{-# DEPRECATED mkTxIx "In favor of `TxIx`" #-}

txIxToInt :: TxIx -> Int
txIxToInt (TxIx w16) = fromIntegral w16
Expand All @@ -843,23 +830,16 @@ mkTxIxPartial i =
fromMaybe (error $ "Value for TxIx is out of a valid range: " ++ show i) $
txIxFromIntegral i

-- | Certificate index. Use `certIxFromIntegral` in order to construct this
-- index safely from anything other than `Word16`. There is also
-- `mkCertIxPartial` that can be used for testing.
newtype CertIx = CertIx {unCertIx :: Word64}
-- | Certificate index. There is `mkCertIxPartial` that can be used for testing when constructing
-- from other integral types that are larger than `Word16`
newtype CertIx = CertIx {unCertIx :: Word16}
deriving stock (Eq, Ord, Show)
deriving newtype (NFData, Enum, Bounded, NoThunks, EncCBOR, ToCBOR, FromCBOR, ToJSON)

instance DecCBOR CertIx where
decCBOR =
ifDecoderVersionAtLeast
(natVersion @9)
(CertIx . fromIntegral @Word16 @Word64 <$> decCBOR)
(CertIx <$> decCBOR)
deriving newtype (NFData, Enum, Bounded, NoThunks, EncCBOR, DecCBOR, ToCBOR, FromCBOR, ToJSON)

-- | Construct a `CertIx` from a 16 bit unsigned integer
mkCertIx :: Word16 -> CertIx
mkCertIx = CertIx . fromIntegral
{-# DEPRECATED mkCertIx "In favor of `CertIx`" #-}

certIxToInt :: CertIx -> Int
certIxToInt (CertIx w16) = fromIntegral w16
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -588,8 +588,8 @@ instance IsConwayUniv fn => HasSpec fn Ptr

instance HasSimpleRep CertIx where
type SimpleRep CertIx = Word16
toSimpleRep (CertIx w) = fromIntegral w
fromSimpleRep = mkCertIx
toSimpleRep = unCertIx
fromSimpleRep = CertIx
instance IsConwayUniv fn => HasSpec fn CertIx

instance HasSimpleRep (Credential r)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2501,7 +2501,7 @@ pcTxId (TxId safehash) = trim (ppSafeHash safehash)
instance PrettyA TxId where prettyA = pcTxId

pcTxIn :: TxIn -> PDoc
pcTxIn (TxIn (TxId h) (TxIx i)) = parens (hsep [ppString "TxIn", trim (ppSafeHash h), ppWord64 i])
pcTxIn (TxIn (TxId h) (TxIx i)) = parens (hsep [ppString "TxIn", trim (ppSafeHash h), ppWord16 i])

instance PrettyA TxIn where prettyA = pcTxIn

Expand Down

0 comments on commit 622bde1

Please sign in to comment.