Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@ repository cardano-haskell-packages

-- See CONTRIBUTING.md for information about when and how to update these.
index-state:
, hackage.haskell.org 2025-06-11T21:55:55Z
, cardano-haskell-packages 2025-06-12T11:07:25Z
, hackage.haskell.org 2025-09-22T06:47:49Z
, cardano-haskell-packages 2025-09-22T06:47:49Z

packages: **/*.cabal

Expand Down
12 changes: 6 additions & 6 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

23 changes: 3 additions & 20 deletions hydra-cardano-api/src/Hydra/Cardano/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ module Hydra.Cardano.Api (
Era,
LedgerEra,
ledgerEraVersion,
LedgerProtocolParameters (..),

-- * Wrapped Types
module Hydra.Cardano.Api,
Expand Down Expand Up @@ -88,25 +87,10 @@ import Cardano.Api.Ledger as X (
import Cardano.Api.Ledger.Lens as X (
mkAdaValue,
)
import Cardano.Api.Shelley as X (
AcquiringFailure (..),
Hash (HeaderHash),
Key (..),
import Cardano.Api.Shelley (
LedgerProtocolParameters,
PlutusScriptOrReferenceInput (PScript),
PoolId,
ShelleyGenesis (..),
ShelleyLedgerEra,
SigningKey (..),
StakeCredential (..),
VerificationKey (..),
fromAlonzoCostModels,
fromAlonzoPrices,
fromPlutusData,
fromShelleyMetadata,
toAlonzoPrices,
toPlutusData,
toShelleyMetadata,
toShelleyNetwork,
)
import Cardano.Api.UTxO (
UTxO,
Expand All @@ -116,7 +100,6 @@ import Cardano.Ledger.Coin as X (Coin (..))
import Hydra.Cardano.Api.Prelude (
Era,
LedgerEra,
LedgerProtocolParameters,
Map,
ledgerEraVersion,
)
Expand All @@ -136,7 +119,7 @@ import Hydra.Cardano.Api.ScriptData as Extras
import Hydra.Cardano.Api.ScriptDatum as Extras
import Hydra.Cardano.Api.ScriptHash as Extras
import Hydra.Cardano.Api.StakeAddress as Extras
import Hydra.Cardano.Api.Tx as Extras hiding (Tx)
import Hydra.Cardano.Api.Tx as Extras
import Hydra.Cardano.Api.TxBody as Extras
import Hydra.Cardano.Api.TxId as Extras
import Hydra.Cardano.Api.TxIn as Extras
Expand Down
3 changes: 2 additions & 1 deletion hydra-cardano-api/src/Hydra/Cardano/Api/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,10 @@

module Hydra.Cardano.Api.Address where

import Hydra.Cardano.Api.Prelude
import Cardano.Api (Address, ByronAddr)

import Test.Gen.Cardano.Api.Typed (genAddressByron)
import Test.QuickCheck (Arbitrary (..))
import Test.QuickCheck.Hedgehog (hedgehog)

-- * Orphans
Expand Down
8 changes: 6 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/AddressInEra.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
module Hydra.Cardano.Api.AddressInEra where

import Hydra.Cardano.Api.Prelude
import Hydra.Cardano.Api.Prelude (unsafeHashFromBytes)

import Cardano.Api (Address (..), AddressInEra (..), AddressTypeInEra (..), IsPlutusScriptLanguage, IsShelleyBasedEra, NetworkId, PaymentCredential (..), PaymentKey, PlutusScript, StakeAddressReference (..), VerificationKey (..), hashScript, makeShelleyAddressInEra, plutusScriptVersion, shelleyBasedEra, verificationKeyHash)
import Cardano.Api qualified as Api
import Cardano.Api.Shelley (fromShelleyAddrIsSbe)
import Cardano.Ledger.Address qualified as Ledger
import Cardano.Ledger.BaseTypes qualified as Ledger
import Cardano.Ledger.Credential qualified as Ledger
Expand Down Expand Up @@ -50,7 +53,8 @@ mkScriptAddress networkId script =
makeShelleyAddressInEra
shelleyBasedEra
networkId
(PaymentCredentialByScript $ hashScript $ PlutusScript version script)
-- Erik TODO: The qualified `Api.PlutusScript` may not be needed when all re-exports are removed.
(PaymentCredentialByScript $ hashScript $ Api.PlutusScript version script)
NoStakeAddress
where
version = plutusScriptVersion @lang
Expand Down
3 changes: 2 additions & 1 deletion hydra-cardano-api/src/Hydra/Cardano/Api/BlockHeader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,9 @@ module Hydra.Cardano.Api.BlockHeader where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (BlockHeader (..), BlockNo (..), Hash, SlotNo (..), deserialiseFromRawBytes, proxyToAsType)
import Data.ByteString qualified as BS
import Test.QuickCheck (vectorOf)
import Test.QuickCheck (Arbitrary (..), Gen, vectorOf)

-- * Generators

Expand Down
5 changes: 2 additions & 3 deletions hydra-cardano-api/src/Hydra/Cardano/Api/ChainPoint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,9 @@

module Hydra.Cardano.Api.ChainPoint where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (BlockHeader (..), ChainPoint (..), SlotNo (..))
import Hydra.Cardano.Api.BlockHeader (genBlockHeaderHash)
import Test.QuickCheck (frequency)
import Test.QuickCheck (Arbitrary (..), Gen, frequency)

-- | Get the chain point corresponding to a given 'BlockHeader'.
getChainPoint :: BlockHeader -> ChainPoint
Expand Down
4 changes: 2 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/ExecutionUnits.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Hydra.Cardano.Api.ExecutionUnits where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (ExecutionUnits)
import Cardano.Api.Shelley (toAlonzoExUnits)
import Cardano.Ledger.Alonzo.Scripts qualified as Ledger

-- * Type Conversions
Expand Down
2 changes: 2 additions & 0 deletions hydra-cardano-api/src/Hydra/Cardano/Api/Hash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ module Hydra.Cardano.Api.Hash where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (PaymentKey, ScriptData, SerialiseAsCBOR, deserialiseFromCBOR, proxyToAsType, serialiseToCBOR)
import Cardano.Api.Shelley (Hash (..))
import Cardano.Ledger.Hashes (unsafeMakeSafeHash)
import Cardano.Ledger.Keys qualified as Ledger
import Cardano.Ledger.Plutus.TxInfo (transKeyHash)
Expand Down
5 changes: 3 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/NetworkId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,10 @@ module Hydra.Cardano.Api.NetworkId where

import Hydra.Cardano.Api.Prelude

import Data.Aeson (Value (String), object, withObject, (.:), (.=))
import Cardano.Api (NetworkId (..))
import Data.Aeson (FromJSON (..), ToJSON (..), Value (String), object, withObject, (.:), (.=))
import Hydra.Cardano.Api.NetworkMagic ()
import Test.QuickCheck (oneof)
import Test.QuickCheck (Arbitrary (..), oneof)

-- * Orphans

Expand Down
3 changes: 2 additions & 1 deletion hydra-cardano-api/src/Hydra/Cardano/Api/PolicyAssets.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,8 @@

module Hydra.Cardano.Api.PolicyAssets where

import Hydra.Cardano.Api.Prelude
import Cardano.Api (PolicyAssets (..))
import Data.Aeson (FromJSON (..), ToJSON (..))

-- * Orphans

Expand Down
5 changes: 3 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/PolicyId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,15 @@

module Hydra.Cardano.Api.PolicyId where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (AsType (..), PolicyId (..), deserialiseFromRawBytes)
import Cardano.Api.Shelley (toShelleyScriptHash)
import Cardano.Ledger.Alonzo.Plutus.TxInfo qualified as Ledger
import Cardano.Ledger.Mary.Value qualified as Ledger
import Data.Aeson (FromJSONKey (..), ToJSONKey (..))
import Hydra.Cardano.Api.ScriptHash ()
import PlutusLedgerApi.V3 (CurrencySymbol, fromBuiltin, unCurrencySymbol)
import Test.Gen.Cardano.Api.Typed (genPolicyId)
import Test.QuickCheck (Arbitrary (..))
import Test.QuickCheck.Hedgehog (hedgehog)

-- * Orphans
Expand Down
19 changes: 2 additions & 17 deletions hydra-cardano-api/src/Hydra/Cardano/Api/Prelude.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
module Hydra.Cardano.Api.Prelude (
module Cardano.Api,
module Cardano.Api.Shelley,
module Data.Aeson,
HasCallStack,
Proxy (..),
Typeable,
Expand All @@ -19,25 +16,14 @@ module Hydra.Cardano.Api.Prelude (
Map,
Set,
unsafeHashFromBytes,
Arbitrary (..),
Gen,
) where

import Cardano.Api hiding (
UTxO,
scriptLanguageSupportedInEra,
toLedgerUTxO,
)
import Cardano.Api.Shelley hiding (
UTxO,
scriptLanguageSupportedInEra,
toLedgerUTxO,
)
import Cardano.Api (ConwayEra)
import Cardano.Api.Shelley (ShelleyLedgerEra)
import Cardano.Api.UTxO (UTxO, UTxO' (..))
import Cardano.Crypto.Hash.Class qualified as CC
import Cardano.Ledger.Binary qualified as Ledger
import Cardano.Ledger.Core qualified as Ledger
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.ByteString (ByteString)
import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.Map (Map)
Expand All @@ -47,7 +33,6 @@ import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Typeable (Typeable)
import GHC.Stack (HasCallStack)
import Test.QuickCheck (Arbitrary (..), Gen)

type Era = ConwayEra

Expand Down
1 change: 1 addition & 0 deletions hydra-cardano-api/src/Hydra/Cardano/Api/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Hydra.Cardano.Api.Pretty where
import Hydra.Cardano.Api qualified as Api
import Hydra.Cardano.Api.Prelude

import Cardano.Api (ScriptDataJsonSchema (..), Tx (..), TxOutDatum (..), getTxBodyContent, getTxId, hashScript, renderTxIn, renderValue, scriptDataToJson, serialiseToRawBytesHexText, txExtraKeyWits, txFee, txIns, txInsCollateral, txInsReference, txMetadata, txMintValue, txMintValueToValue, txOuts, txReturnCollateral, txTotalCollateral, txValidityLowerBound, txValidityUpperBound)
import Cardano.Api.UTxO qualified as UTxO
import Cardano.Binary (serialize)
import Cardano.Ledger.Alonzo.Scripts qualified as Ledger
Expand Down
9 changes: 7 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/ReferenceScript.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,15 @@
module Hydra.Cardano.Api.ReferenceScript where

import Hydra.Cardano.Api.Prelude
import Hydra.Cardano.Api.Prelude (Era)

import Cardano.Api (IsPlutusScriptLanguage, PlutusScript, babbageBasedEra, plutusScriptVersion, toScriptInAnyLang)
import Cardano.Api qualified as Api
import Cardano.Api.Shelley (ReferenceScript (..))

-- | Construct a 'ReferenceScript' from any given Plutus script.
mkScriptRef :: IsPlutusScriptLanguage lang => PlutusScript lang -> ReferenceScript Era
mkScriptRef =
ReferenceScript babbageBasedEra
. toScriptInAnyLang
. PlutusScript plutusScriptVersion
-- Erik TODO: The qualified `Api.PlutusScript` may not be needed when all re-exports are removed.
. Api.PlutusScript plutusScriptVersion
4 changes: 2 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/ScriptData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@

module Hydra.Cardano.Api.ScriptData where

import Hydra.Cardano.Api.Prelude hiding (left)

import Cardano.Api (CtxTx, HashableScriptData, TxOut (..), TxOutDatum (..), getScriptData, unsafeHashableScriptData)
import Cardano.Api.Shelley (fromAlonzoData, fromPlutusData, toAlonzoData, toPlutusData)
import Cardano.Ledger.Core qualified as Ledger
import Cardano.Ledger.Plutus.Data qualified as Ledger
import PlutusLedgerApi.V3 qualified as Plutus
Expand Down
2 changes: 1 addition & 1 deletion hydra-cardano-api/src/Hydra/Cardano/Api/ScriptDatum.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Hydra.Cardano.Api.ScriptDatum where

import Hydra.Cardano.Api.Prelude
import Cardano.Api (ScriptDatum (..), WitCtxTxIn)

import Hydra.Cardano.Api.ScriptData (ToScriptData, toScriptData)

Expand Down
2 changes: 1 addition & 1 deletion hydra-cardano-api/src/Hydra/Cardano/Api/ScriptHash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

module Hydra.Cardano.Api.ScriptHash where

import Hydra.Cardano.Api.Prelude
import Cardano.Api (ScriptHash, ScriptInAnyLang (..), hashScript)

-- * Extras

Expand Down
6 changes: 4 additions & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/StakeAddress.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
module Hydra.Cardano.Api.StakeAddress where

import Hydra.Cardano.Api.Prelude
import Cardano.Api (IsPlutusScriptLanguage (..), NetworkId, PlutusScript, StakeAddress, hashScript, makeStakeAddress)
import Cardano.Api qualified as Api
import Cardano.Api.Shelley (StakeCredential (StakeCredentialByScript))

-- | Construct a stake address from a Plutus script.
mkScriptStakeAddress ::
Expand All @@ -10,6 +12,6 @@ mkScriptStakeAddress ::
PlutusScript lang ->
StakeAddress
mkScriptStakeAddress networkId script =
makeStakeAddress networkId $ StakeCredentialByScript $ hashScript $ PlutusScript version script
makeStakeAddress networkId $ StakeCredentialByScript $ hashScript $ Api.PlutusScript version script
where
version = plutusScriptVersion @lang
18 changes: 15 additions & 3 deletions hydra-cardano-api/src/Hydra/Cardano/Api/Tx.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,26 @@
module Hydra.Cardano.Api.Tx (
-- * Extras
module Hydra.Cardano.Api.Tx,

-- * Re-export normal Tx (any era)
Tx,
)
where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (
IsShelleyBasedEra,
PaymentKey,
ShelleyWitnessSigningKey (..),
SigningKey (..),
Tx (..),
TxBodyContent (..),
getTxBody,
getTxBodyContent,
makeShelleyKeyWitness,
makeSignedTransaction,
shelleyBasedEra,
toCtxUTxOTxOut,
)
import Cardano.Api.Shelley (ShelleyLedgerEra, Tx (ShelleyTx))
import Cardano.Api.UTxO qualified as UTxO
import Cardano.Ledger.Api (
EraTx (mkBasicTx),
Expand Down
1 change: 1 addition & 0 deletions hydra-cardano-api/src/Hydra/Cardano/Api/TxBody.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Hydra.Cardano.Api.TxBody where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (Tx (..), TxBody (..), TxBodyScriptData (..), TxIn (..), getTxBody)
import Cardano.Ledger.Alonzo.TxWits qualified as Ledger
import Cardano.Ledger.Api (
AsItem (..),
Expand Down
3 changes: 1 addition & 2 deletions hydra-cardano-api/src/Hydra/Cardano/Api/TxId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,7 @@

module Hydra.Cardano.Api.TxId where

import Hydra.Cardano.Api.Prelude

import Cardano.Api (AsType (..), TxId (..), deserialiseFromRawBytes, serialiseToRawBytes)
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Crypto.Hash.Class qualified as CC
import Cardano.Ledger.Hashes qualified as Ledger
Expand Down
Loading