{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Cardano.Ledger.TxIn
( TxId (..),
TxIn (TxIn),
mkTxInPartial,
TxIx,
txid,
)
where
import Cardano.Binary (FromCBOR (fromCBOR), ToCBOR (..), encodeListLen)
import Cardano.Crypto.Hash.Class (HashAlgorithm)
import Cardano.Ledger.BaseTypes (TxIx (..), mkTxIxPartial)
import Cardano.Ledger.Core (TxBody)
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Hashes (EraIndependentTxBody)
import Cardano.Ledger.SafeHash (HashAnnotated, SafeHash, hashAnnotated)
import Cardano.Ledger.Serialization (decodeRecordNamed)
import Cardano.Prelude (HeapWords (..))
import qualified Cardano.Prelude as HW
import Control.DeepSeq (NFData)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
txid ::
forall era c.
( HashAlgorithm (CC.HASH c),
HashAnnotated (TxBody era) EraIndependentTxBody c
) =>
TxBody era ->
TxId c
txid :: TxBody era -> TxId c
txid = SafeHash c EraIndependentTxBody -> TxId c
forall crypto. SafeHash crypto EraIndependentTxBody -> TxId crypto
TxId (SafeHash c EraIndependentTxBody -> TxId c)
-> (TxBody era -> SafeHash c EraIndependentTxBody)
-> TxBody era
-> TxId c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxBody era -> SafeHash c EraIndependentTxBody
forall c i x.
(HasAlgorithm c, HashAnnotated x i c) =>
x -> SafeHash c i
hashAnnotated
newtype TxId crypto = TxId {TxId crypto -> SafeHash crypto EraIndependentTxBody
_unTxId :: SafeHash crypto EraIndependentTxBody}
deriving (Int -> TxId crypto -> ShowS
[TxId crypto] -> ShowS
TxId crypto -> String
(Int -> TxId crypto -> ShowS)
-> (TxId crypto -> String)
-> ([TxId crypto] -> ShowS)
-> Show (TxId crypto)
forall crypto. Int -> TxId crypto -> ShowS
forall crypto. [TxId crypto] -> ShowS
forall crypto. TxId crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxId crypto] -> ShowS
$cshowList :: forall crypto. [TxId crypto] -> ShowS
show :: TxId crypto -> String
$cshow :: forall crypto. TxId crypto -> String
showsPrec :: Int -> TxId crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> TxId crypto -> ShowS
Show, TxId crypto -> TxId crypto -> Bool
(TxId crypto -> TxId crypto -> Bool)
-> (TxId crypto -> TxId crypto -> Bool) -> Eq (TxId crypto)
forall crypto. TxId crypto -> TxId crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxId crypto -> TxId crypto -> Bool
$c/= :: forall crypto. TxId crypto -> TxId crypto -> Bool
== :: TxId crypto -> TxId crypto -> Bool
$c== :: forall crypto. TxId crypto -> TxId crypto -> Bool
Eq, Eq (TxId crypto)
Eq (TxId crypto)
-> (TxId crypto -> TxId crypto -> Ordering)
-> (TxId crypto -> TxId crypto -> Bool)
-> (TxId crypto -> TxId crypto -> Bool)
-> (TxId crypto -> TxId crypto -> Bool)
-> (TxId crypto -> TxId crypto -> Bool)
-> (TxId crypto -> TxId crypto -> TxId crypto)
-> (TxId crypto -> TxId crypto -> TxId crypto)
-> Ord (TxId crypto)
TxId crypto -> TxId crypto -> Bool
TxId crypto -> TxId crypto -> Ordering
TxId crypto -> TxId crypto -> TxId crypto
forall crypto. Eq (TxId crypto)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall crypto. TxId crypto -> TxId crypto -> Bool
forall crypto. TxId crypto -> TxId crypto -> Ordering
forall crypto. TxId crypto -> TxId crypto -> TxId crypto
min :: TxId crypto -> TxId crypto -> TxId crypto
$cmin :: forall crypto. TxId crypto -> TxId crypto -> TxId crypto
max :: TxId crypto -> TxId crypto -> TxId crypto
$cmax :: forall crypto. TxId crypto -> TxId crypto -> TxId crypto
>= :: TxId crypto -> TxId crypto -> Bool
$c>= :: forall crypto. TxId crypto -> TxId crypto -> Bool
> :: TxId crypto -> TxId crypto -> Bool
$c> :: forall crypto. TxId crypto -> TxId crypto -> Bool
<= :: TxId crypto -> TxId crypto -> Bool
$c<= :: forall crypto. TxId crypto -> TxId crypto -> Bool
< :: TxId crypto -> TxId crypto -> Bool
$c< :: forall crypto. TxId crypto -> TxId crypto -> Bool
compare :: TxId crypto -> TxId crypto -> Ordering
$ccompare :: forall crypto. TxId crypto -> TxId crypto -> Ordering
$cp1Ord :: forall crypto. Eq (TxId crypto)
Ord, (forall x. TxId crypto -> Rep (TxId crypto) x)
-> (forall x. Rep (TxId crypto) x -> TxId crypto)
-> Generic (TxId crypto)
forall x. Rep (TxId crypto) x -> TxId crypto
forall x. TxId crypto -> Rep (TxId crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (TxId crypto) x -> TxId crypto
forall crypto x. TxId crypto -> Rep (TxId crypto) x
$cto :: forall crypto x. Rep (TxId crypto) x -> TxId crypto
$cfrom :: forall crypto x. TxId crypto -> Rep (TxId crypto) x
Generic)
deriving newtype (Context -> TxId crypto -> IO (Maybe ThunkInfo)
Proxy (TxId crypto) -> String
(Context -> TxId crypto -> IO (Maybe ThunkInfo))
-> (Context -> TxId crypto -> IO (Maybe ThunkInfo))
-> (Proxy (TxId crypto) -> String)
-> NoThunks (TxId crypto)
forall crypto. Context -> TxId crypto -> IO (Maybe ThunkInfo)
forall crypto. Proxy (TxId crypto) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (TxId crypto) -> String
$cshowTypeOf :: forall crypto. Proxy (TxId crypto) -> String
wNoThunks :: Context -> TxId crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall crypto. Context -> TxId crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> TxId crypto -> IO (Maybe ThunkInfo)
$cnoThunks :: forall crypto. Context -> TxId crypto -> IO (Maybe ThunkInfo)
NoThunks, TxId crypto -> Int
(TxId crypto -> Int) -> HeapWords (TxId crypto)
forall crypto. TxId crypto -> Int
forall a. (a -> Int) -> HeapWords a
heapWords :: TxId crypto -> Int
$cheapWords :: forall crypto. TxId crypto -> Int
HeapWords)
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 CC.Crypto crypto => HeapWords (TxIn crypto) where
heapWords :: TxIn crypto -> Int
heapWords (TxIn TxId crypto
txId TxIx
_) =
Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ TxId crypto -> Int
forall a. HeapWords a => a -> Int
HW.heapWords TxId crypto
txId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
data TxIn crypto = TxIn !(TxId crypto) {-# UNPACK #-} !TxIx
deriving ((forall x. TxIn crypto -> Rep (TxIn crypto) x)
-> (forall x. Rep (TxIn crypto) x -> TxIn crypto)
-> Generic (TxIn crypto)
forall x. Rep (TxIn crypto) x -> TxIn crypto
forall x. TxIn crypto -> Rep (TxIn crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (TxIn crypto) x -> TxIn crypto
forall crypto x. TxIn crypto -> Rep (TxIn crypto) x
$cto :: forall crypto x. Rep (TxIn crypto) x -> TxIn crypto
$cfrom :: forall crypto x. TxIn crypto -> Rep (TxIn crypto) x
Generic)
mkTxInPartial :: HW.HasCallStack => TxId crypto -> Integer -> TxIn crypto
mkTxInPartial :: TxId crypto -> Integer -> TxIn crypto
mkTxInPartial TxId crypto
txId = TxId crypto -> TxIx -> TxIn crypto
forall crypto. TxId crypto -> TxIx -> TxIn crypto
TxIn TxId crypto
txId (TxIx -> TxIn crypto)
-> (Integer -> TxIx) -> Integer -> TxIn crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Integer -> TxIx
Integer -> TxIx
mkTxIxPartial
deriving instance Eq (TxIn crypto)
deriving instance Ord (TxIn crypto)
deriving instance Show (TxIn crypto)
deriving instance CC.Crypto crypto => NFData (TxIn crypto)
instance NoThunks (TxIn crypto)
instance CC.Crypto crypto => ToCBOR (TxIn crypto) where
toCBOR :: TxIn crypto -> Encoding
toCBOR (TxIn TxId crypto
txId TxIx
index) =
Word -> Encoding
encodeListLen Word
2
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> TxId crypto -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR TxId crypto
txId
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> TxIx -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR TxIx
index
instance CC.Crypto crypto => FromCBOR (TxIn crypto) where
fromCBOR :: Decoder s (TxIn crypto)
fromCBOR =
Text
-> (TxIn crypto -> Int)
-> Decoder s (TxIn crypto)
-> Decoder s (TxIn crypto)
forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed
Text
"TxIn"
(Int -> TxIn crypto -> Int
forall a b. a -> b -> a
const Int
2)
(TxId crypto -> TxIx -> TxIn crypto
forall crypto. TxId crypto -> TxIx -> TxIn crypto
TxIn (TxId crypto -> TxIx -> TxIn crypto)
-> Decoder s (TxId crypto) -> Decoder s (TxIx -> TxIn crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (TxId crypto)
forall a s. FromCBOR a => Decoder s a
fromCBOR Decoder s (TxIx -> TxIn crypto)
-> Decoder s TxIx -> Decoder s (TxIn crypto)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s TxIx
forall a s. FromCBOR a => Decoder s a
fromCBOR)