{-# OPTIONS_GHC -Wno-orphans #-}
module Hydra.Cardano.Api.TxId where
import Hydra.Cardano.Api.Prelude
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Crypto.Hash.Class qualified as CC
import Cardano.Ledger.Hashes qualified as Ledger
import Cardano.Ledger.TxIn qualified as Ledger
instance ToCBOR TxId where
toCBOR :: TxId -> Encoding
toCBOR = ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (ByteString -> Encoding)
-> (TxId -> ByteString) -> TxId -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxId -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes
instance FromCBOR TxId where
fromCBOR :: forall s. Decoder s TxId
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
case AsType TxId -> ByteString -> Either SerialiseAsRawBytesError TxId
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
deserialiseFromRawBytes AsType TxId
AsTxId ByteString
bs of
Left SerialiseAsRawBytesError
err -> String -> Decoder s TxId
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SerialiseAsRawBytesError -> String
forall a. Show a => a -> String
show SerialiseAsRawBytesError
err)
Right TxId
v -> TxId -> Decoder s TxId
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TxId
v
toLedgerTxId :: TxId -> Ledger.TxId
toLedgerTxId :: TxId -> TxId
toLedgerTxId (TxId Hash HASH EraIndependentTxBody
h) =
SafeHash EraIndependentTxBody -> TxId
Ledger.TxId (Hash HASH EraIndependentTxBody -> SafeHash EraIndependentTxBody
forall i. Hash HASH i -> SafeHash i
Ledger.unsafeMakeSafeHash (Hash HASH EraIndependentTxBody -> Hash HASH EraIndependentTxBody
forall h a b. Hash h a -> Hash h b
CC.castHash Hash HASH EraIndependentTxBody
h))