Skip to content

Commit

Permalink
Add Cardano.Read.Ledger.Tx.Outputs
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Jul 26, 2024
1 parent 08f877f commit 0cf77ab
Showing 1 changed file with 58 additions and 0 deletions.
58 changes: 58 additions & 0 deletions lib/read/lib/Cardano/Read/Ledger/Tx/Output.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

-- |
-- Copyright: © 2020-2022 IOHK
-- License: Apache-2.0
--
-- Raw era-dependent tx output
--

module Cardano.Read.Ledger.Tx.Output
( OutputType
, Output (..)
)
where

import Prelude

import Cardano.Ledger.Alonzo.TxOut
( AlonzoTxOut
)
import Cardano.Ledger.Babbage.TxOut
( BabbageTxOut
)
import Cardano.Ledger.Shelley.TxOut
( ShelleyTxOut
)
import Cardano.Wallet.Read.Eras
( Allegra
, Alonzo
, Babbage
, Byron
, Conway
, Mary
, Shelley
)

import qualified Cardano.Chain.UTxO as BY

type family OutputType era where
OutputsType Byron = BY.TxOut
OutputsType Shelley = ShelleyTxOut Shelley
OutputsType Allegra = ShelleyTxOut Allegra
OutputsType Mary = ShelleyTxOut Mary
OutputsType Alonzo = AlonzoTxOut Alonzo
OutputsType Babbage = BabbageTxOut Babbage
OutputsType Conway = BabbageTxOut Conway

newtype Output era = Output (OutputType era)

deriving instance Show (OutputType era) => Show (Output era)
deriving instance Eq (OutputType era) => Eq (Output era)

0 comments on commit 0cf77ab

Please sign in to comment.