Skip to content

Commit

Permalink
manually unpack txid in txin
Browse files Browse the repository at this point in the history
  • Loading branch information
redxaxder committed Sep 24, 2021
1 parent c6c4be1 commit a14262f
Show file tree
Hide file tree
Showing 4 changed files with 77 additions and 25 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Expand Up @@ -40,8 +40,8 @@ test-show-details: streaming
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-base
tag: 592aa61d657ad5935a33bace1243abce3728b643
--sha256: 1bgq3a2wfdz24jqfwylcc6jjg5aji8dpy5gjkhpnmkkvgcr2rkyb
tag: 42525d64502f41f4753d9efc98b9a936ac5ba2ac
--sha256: 1mn7ivszn2652vqm8hbkw9fwawf70qh2mzn0lbqig6basc5xdr75
subdir:
base-deriving-via
binary
Expand Down
4 changes: 3 additions & 1 deletion eras/shelley/impl/src/Cardano/Ledger/Pretty.hs
Expand Up @@ -7,6 +7,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}

module Cardano.Ledger.Pretty where

Expand Down Expand Up @@ -139,6 +140,7 @@ import Cardano.Ledger.Shelley.TxBody
TxBodyRaw (..),
TxId (..),
TxIn (..),
viewTxIn,
TxOut (..),
Wdrl (..),
WitVKey (..),
Expand Down Expand Up @@ -1018,7 +1020,7 @@ ppTxId :: TxId c -> PDoc
ppTxId (TxId x) = ppSexp "TxId" [ppSafeHash x]

ppTxIn :: TxIn c -> PDoc
ppTxIn (TxInCompact txid word) = ppSexp "TxIn" [ppTxId txid, ppWord64 word]
ppTxIn (viewTxIn -> (txid, index)) = ppSexp "TxIn" [ppTxId txid, ppNatural index]

ppTxOut :: (Era era, PrettyA (Core.Value era)) => TxOut era -> PDoc
ppTxOut (TxOutCompact caddr cval) = ppSexp "TxOut" [ppCompactAddr caddr, ppCompactForm prettyA cval]
Expand Down
Expand Up @@ -67,7 +67,7 @@ translateCompactTxInByronToShelley ::
Byron.CompactTxIn ->
TxIn c
translateCompactTxInByronToShelley (Byron.CompactTxInUtxo compactTxId idx) =
TxInCompact
TxIn
(translateTxIdByronToShelley (Byron.fromCompactTxId compactTxId))
(fromIntegral idx)

Expand Down
92 changes: 71 additions & 21 deletions eras/shelley/impl/src/Cardano/Ledger/Shelley/TxBody.hs
Expand Up @@ -50,6 +50,7 @@ module Cardano.Ledger.Shelley.TxBody
TxBodyRaw (..),
TxId (..),
TxIn (TxIn, ..),
viewTxIn,
EraIndependentTxBody,
-- eraIndTxBodyHash,
TxOut (TxOut, TxOutCompact),
Expand Down Expand Up @@ -109,7 +110,7 @@ import Cardano.Ledger.Credential
Ptr (..),
StakeCredential,
)
import qualified Cardano.Ledger.Crypto as CC (ADDRHASH, Crypto)
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Era
import Cardano.Ledger.Hashes (EraIndependentTxBody, ScriptHash)
import Cardano.Ledger.Keys
Expand All @@ -129,6 +130,8 @@ import Cardano.Ledger.SafeHash
( HashAnnotated,
SafeHash,
SafeToHash,
unsafeMakeSafeHash,
extractHash,
)
import Cardano.Ledger.Serialization
( CBORGroup (..),
Expand Down Expand Up @@ -203,7 +206,12 @@ import Data.Typeable (Typeable)
import Data.Word (Word64, Word8)
import GHC.Generics (Generic)
import GHC.Records
import NoThunks.Class (AllowThunksIn (..), InspectHeapNamed (..), NoThunks (..))
import NoThunks.Class
( AllowThunksIn (..),
InspectHeapNamed (..),
NoThunks (..),
noThunksInValues
)
import Numeric.Natural (Natural)
import Quiet

Expand Down Expand Up @@ -431,7 +439,10 @@ 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
heapWords (TxInCompact32 a _ _ _ ix) =
6 + (4 * HW.heapWordsUnpacked a) + HW.heapWordsUnpacked ix
heapWords (TxInCompactOther txid ix) =
3 + HW.heapWords txid + HW.heapWordsUnpacked ix

type TransTxId (c :: Type -> Constraint) era =
-- Transaction Ids are the hash of a transaction body, which contains
Expand All @@ -445,31 +456,66 @@ type TransTxId (c :: Type -> Constraint) era =
)

-- | The input of a UTxO.
data TxIn crypto = TxInCompact !(TxId crypto) {-# UNPACK #-} !Word64
deriving (Generic)
data TxIn crypto where
TxInCompact32 ::
HS.SizeHash (CC.HASH crypto) ~ 32
=> {-# UNPACK #-} !Word64 -- Hash part 1/4
-> {-# UNPACK #-} !Word64 -- Hash part 2/4
-> {-# UNPACK #-} !Word64 -- Hash part 3/4
-> {-# UNPACK #-} !Word64 -- Hash part 4/4
-> {-# UNPACK #-} !Word64 -- Index
-> TxIn crypto
TxInCompactOther :: !(TxId crypto) -> {-# UNPACK #-} !Word64 -> TxIn crypto

pattern TxIn ::
CC.Crypto crypto =>
TxId crypto ->
Natural -> -- TODO We might want to change this to Word64 generally
TxIn crypto
pattern TxIn addr index <-
TxInCompact addr (fromIntegral -> index)
pattern TxIn txid index <- (viewTxIn -> (txid, index))
where
TxIn addr index =
TxInCompact addr (fromIntegral index)

TxIn txid@(TxId sh) index =
case HS.viewHash32 (extractHash sh) of
HS.ViewHashNot32 -> TxInCompactOther txid (fromIntegral index)
HS.ViewHash32 a b c d -> TxInCompact32 a b c d (fromIntegral index)
{-# COMPLETE TxIn #-}

deriving instance Ord (TxIn crypto)

deriving instance Eq (TxIn crypto)

deriving instance Show (TxIn crypto)

deriving instance CC.Crypto crypto => NFData (TxIn crypto)

instance NoThunks (TxIn crypto)
viewTxIn :: TxIn crypto -> (TxId crypto, Natural)
viewTxIn (TxInCompactOther txid i) = (txid, fromIntegral i)
viewTxIn (TxInCompact32 a b c d i) = (txid, fromIntegral i)
where
txid = TxId (unsafeMakeSafeHash $ HS.unsafeMkHash32 a b c d)

instance Show (TxIn crypto) where
showsPrec d (viewTxIn -> (txid, ix)) = showParen (d > app_prec) $
showString "TxId "
. showsPrec (app_prec+1) txid
. showString " "
. showsPrec (app_prec+1) ix
where
app_prec = 10

instance Ord (TxIn crypto) where
compare (TxInCompact32 a1 b1 c1 d1 i1) (TxInCompact32 a2 b2 c2 d2 i2) =
compare a1 a2 <> compare b1 b2 <> compare c1 c2 <> compare d1 d2
<> compare i1 i2
compare (viewTxIn -> (id1, ix1)) (viewTxIn -> (id2, ix2)) =
compare id1 id2 <> compare ix1 ix2

instance Eq (TxIn crypto) where
(==) (TxInCompact32 a1 b1 c1 d1 i1) (TxInCompact32 a2 b2 c2 d2 i2) =
(a1 == a2) && (b1 == b2) && (c1 == c2) && (d1 == d2) && (i1 == i2)
(==) (viewTxIn -> (id1, ix1)) (viewTxIn -> (id2, ix2)) =
(id1 == id2) && (ix1 == ix2)

instance CC.Crypto crypto => NFData (TxIn crypto) where
rnf (TxInCompactOther txid _) = seq (rnf txid) ()
rnf (TxInCompact32 _ _ _ _ _) = ()

instance NoThunks (TxIn crypto) where
showTypeOf _ = "TxIn"
wNoThunks c (TxInCompactOther txid _) = noThunksInValues c [txid]
wNoThunks _ (TxInCompact32 _ _ _ _ _) = pure Nothing -- always in normal form

-- | The output of a UTxO.
data TxOut era
Expand Down Expand Up @@ -1057,7 +1103,7 @@ instance
CC.Crypto crypto =>
ToCBOR (TxIn crypto)
where
toCBOR (TxInCompact txId index) =
toCBOR (viewTxIn -> (txId, index)) =
encodeListLen 2
<> toCBOR txId
<> toCBOR index
Expand All @@ -1067,7 +1113,11 @@ instance
FromCBOR (TxIn crypto)
where
fromCBOR =
decodeRecordNamed "TxIn" (const 2) (TxInCompact <$> fromCBOR <*> fromCBOR)
decodeRecordNamed "TxIn" (const 2)
(TxIn <$> fromCBOR <*> fmap natural fromCBOR)
where
natural :: Word64 -> Natural
natural = fromIntegral

instance-- use the weakest constraint necessary

Expand Down

0 comments on commit a14262f

Please sign in to comment.