Skip to content

Commit

Permalink
bump dependencies for cardano-node 8.10.0-pre
Browse files Browse the repository at this point in the history
  • Loading branch information
disassembler committed May 6, 2024
1 parent ba2a8d9 commit 890d4d0
Show file tree
Hide file tree
Showing 10 changed files with 459 additions and 344 deletions.
8 changes: 4 additions & 4 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ repository cardano-haskell-packages
-- See CONTRIBUTING for information about these, including some Nix commands
-- you need to run if you change them
index-state:
, hackage.haskell.org 2023-07-10T14:55:34Z
, cardano-haskell-packages 2023-09-07T16:00:00Z
, hackage.haskell.org 2024-03-26T06:28:59Z
, cardano-haskell-packages 2024-05-06T13:38:48Z

packages:
cardano-faucet
Expand Down Expand Up @@ -53,7 +53,7 @@ package cardano-faucet
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-addresses
tag: ca49ed0a7e8c1205f270099a28ee6659cd1a22d7
--sha256: sha256-7IxvCwWC/2h87D+/l7Mu0hHoQMTZir03iFLukaE5FP8=
tag: ed83fe7457da9adb53bb92acd0e79c321bd25646
--sha256: sha256-saxnZMeeZcASesw2Fgg9X0I8YFQ7p8jD25TMt782i2s=
subdir: command-line
core
6 changes: 3 additions & 3 deletions cardano-faucet/cardano-faucet.cabal
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
cabal-version: 3.0

name: cardano-faucet
version: 8.3
version: 8.10
description: The Cardano command-line interface.
author: IOHK
maintainer: operations@iohk.io
Expand Down Expand Up @@ -61,8 +61,8 @@ library
, MissingH
, bytestring
, cardano-addresses
, cardano-api
, cardano-cli ^>= 8.6.1.0
, cardano-api ^>= 8.45.2
, cardano-cli ^>= 8.23
, cardano-prelude
, containers
, either
Expand Down
155 changes: 48 additions & 107 deletions cardano-faucet/src/Cardano/Faucet.hs

Large diffs are not rendered by default.

27 changes: 12 additions & 15 deletions cardano-faucet/src/Cardano/Faucet/Misc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,25 +2,27 @@

module Cardano.Faucet.Misc where

import Cardano.Api (ConsensusModeParams(CardanoModeParams), CardanoMode, EpochSlots(EpochSlots), AddressAny, parseAddressAny, TxOutValue(TxOutAdaOnly, TxOutValue), CardanoEra, EraInMode, toEraInMode, ConsensusMode(CardanoMode),AssetId(AdaAssetId), Quantity, valueToList)
import Cardano.Api.Shelley (Lovelace, selectLovelace, AssetId(AssetId))
import Cardano.Api (ConsensusModeParams(CardanoModeParams), EpochSlots(EpochSlots), AddressAny, parseAddressAny, TxOutValue(..), AssetId(AdaAssetId), Quantity, fromLedgerValue, valueToList)
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (selectLovelace, AssetId(AssetId))
import Cardano.Faucet.Types
import Cardano.Prelude
import Control.Monad.Trans.Except.Extra (left)
import Data.Text qualified as T
import Text.Parsec

getValue :: TxOutValue era -> FaucetValue
getValue (TxOutAdaOnly _ ll) = Ada ll
getValue (TxOutValue _ val) = convertRemaining remaining
getValue (TxOutValueByron ll) = Ada ll
getValue (TxOutValueShelleyBased sbe val) = convertRemaining remaining
where
ll :: Lovelace
ll = selectLovelace val
apiValue = fromLedgerValue sbe val
ll :: L.Coin
ll = selectLovelace apiValue
isntAda :: (AssetId, Quantity) -> Bool
isntAda (AdaAssetId, _) = False
isntAda (AssetId _ _, _) = True
remaining :: [(AssetId, Quantity)]
remaining = filter isntAda (valueToList val)
remaining = filter isntAda (valueToList apiValue)
convertRemaining :: [(AssetId, Quantity)] -> FaucetValue
convertRemaining [t] = FaucetValueMultiAsset ll (FaucetToken t)
convertRemaining [] = Ada ll
Expand All @@ -37,7 +39,7 @@ stripMintingTokens (FaucetValueMultiAsset ll (FaucetMintToken _)) = Ada ll
stripMintingTokens fv@(FaucetValueManyTokens _) = fv

-- returns just the lovelace component and ignores tokens
faucetValueToLovelace :: FaucetValue -> Lovelace
faucetValueToLovelace :: FaucetValue -> L.Coin
faucetValueToLovelace (Ada ll) = ll
faucetValueToLovelace (FaucetValueMultiAsset ll _token) = ll
faucetValueToLovelace (FaucetValueManyTokens ll) = ll
Expand All @@ -47,13 +49,8 @@ parseAddress addr = case parse (parseAddressAny <* eof) "" (T.unpack addr) of
Right a -> return $ a
Left e -> left $ FaucetWebErrorInvalidAddress addr (show e)

defaultCModeParams :: ConsensusModeParams CardanoMode
defaultCModeParams :: ConsensusModeParams
defaultCModeParams = CardanoModeParams (EpochSlots defaultByronEpochSlots)

defaultByronEpochSlots :: Word64
defaultByronEpochSlots = 21600

convertEra :: Monad m => CardanoEra era -> ExceptT FaucetWebError m (EraInMode era CardanoMode)
convertEra era = case (toEraInMode era CardanoMode) of
Just eraInMode -> pure eraInMode
Nothing -> left $ FaucetWebErrorEraConversion
defaultByronEpochSlots = 21600
44 changes: 23 additions & 21 deletions cardano-faucet/src/Cardano/Faucet/TxUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,24 +4,25 @@

module Cardano.Faucet.TxUtils where

import Cardano.Api (Lovelace, IsShelleyBasedEra, ShelleyBasedEra, TxIn, TxOut(TxOut), CtxUTxO, TxBody, TxBodyContent(TxBodyContent), Witness(KeyWitness), KeyWitnessInCtx(KeyWitnessForSpending), TxInsCollateral(TxInsCollateralNone), TxInsReference(TxInsReferenceNone), TxTotalCollateral(TxTotalCollateralNone), TxReturnCollateral(TxReturnCollateralNone), TxMetadataInEra(TxMetadataNone), TxAuxScripts(TxAuxScriptsNone), TxExtraKeyWitnesses(TxExtraKeyWitnessesNone), TxWithdrawals(TxWithdrawalsNone), TxCertificates, BuildTxWith(BuildTxWith), TxUpdateProposal(TxUpdateProposalNone), TxMintValue(..), TxScriptValidity(TxScriptValidityNone), shelleyBasedToCardanoEra, Tx, makeShelleyKeyWitness, makeSignedTransaction, TxId, getTxId, BuildTx, ShelleyWitnessSigningKey, AddressAny)
import Cardano.Api.Shelley (lovelaceToValue, Value, createAndValidateTransactionBody, TxGovernanceActions(TxGovernanceActionsNone), TxVotes(TxVotesNone))
import Cardano.Api (ShelleyBasedEra, TxIn, TxOut(TxOut), CtxUTxO, TxBody, TxBodyContent(TxBodyContent), Witness(KeyWitness), KeyWitnessInCtx(KeyWitnessForSpending), TxInsCollateral(TxInsCollateralNone), TxInsReference(TxInsReferenceNone), TxTotalCollateral(TxTotalCollateralNone), TxReturnCollateral(TxReturnCollateralNone), TxMetadataInEra(TxMetadataNone), TxAuxScripts(TxAuxScriptsNone), TxExtraKeyWitnesses(TxExtraKeyWitnessesNone), TxWithdrawals(TxWithdrawalsNone), TxCertificates, BuildTxWith(BuildTxWith), TxUpdateProposal(TxUpdateProposalNone), TxMintValue(..), TxScriptValidity(TxScriptValidityNone), defaultTxValidityUpperBound, docToText, Tx, makeShelleyKeyWitness, makeSignedTransaction, TxId, getTxId, BuildTx, ShelleyWitnessSigningKey, AddressAny, TxValidityLowerBound (TxValidityNoLowerBound))
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (lovelaceToValue, Value, createAndValidateTransactionBody)
import Cardano.Faucet.Misc (getValue, faucetValueToLovelace)
import Cardano.Faucet.Types (FaucetWebError(..), FaucetValue)
import Cardano.Faucet.Utils
import Cardano.Prelude hiding ((%))
import Control.Monad.Trans.Except.Extra (left)
import Cardano.CLI.Types.Common
import Cardano.CLI.Legacy.Run.Transaction
import Cardano.CLI.Types.Errors.ShelleyTxCmdError
import Cardano.CLI.EraBased.Run.Transaction
import Cardano.CLI.Types.Errors.TxCmdError

getMintedValue :: TxMintValue BuildTx era -> Value
getMintedValue (TxMintValue _ val _) = val
getMintedValue (TxMintNone) = mempty

newtype Fee = Fee Lovelace
newtype Fee = Fee L.Coin

txBuild :: IsShelleyBasedEra era
txBuild :: ()
=> ShelleyBasedEra era
-> (TxIn, TxOut CtxUTxO era)
-> Either AddressAny [TxOutAnyEra]
Expand All @@ -32,12 +33,11 @@ txBuild :: IsShelleyBasedEra era
txBuild sbe (txin, txout) addressOrOutputs certs minting (Fee fixedFee) = do
let
--localNodeConnInfo = LocalNodeConnectInfo cModeParams networkId sockPath
era = shelleyBasedToCardanoEra sbe
unwrap :: TxOut ctx1 era1 -> FaucetValue
unwrap (TxOut _ val _ _) = getValue val
value :: Lovelace
value :: L.Coin
value = faucetValueToLovelace $ unwrap txout
change :: Lovelace
change :: L.Coin
change = value - fixedFee
mintedValue = getMintedValue minting
-- TODO, add minted tokens
Expand All @@ -52,11 +52,12 @@ txBuild sbe (txin, txout) addressOrOutputs certs minting (Fee fixedFee) = do
<$> pure [(txin, BuildTxWith $ KeyWitness KeyWitnessForSpending)]
<*> pure TxInsCollateralNone
<*> pure TxInsReferenceNone
<*> mapM (\x -> withExceptT (FaucetWebErrorTodo . renderShelleyTxCmdError) $ toTxOutInAnyEra era x) (getTxOuts addressOrOutputs)
<*> mapM (\x -> withExceptT (FaucetWebErrorTodo . docToText . renderTxCmdError) $ toTxOutInAnyEra sbe x) (getTxOuts addressOrOutputs)
<*> pure TxTotalCollateralNone
<*> pure TxReturnCollateralNone
<*> validateTxFee era (Just fixedFee)
<*> noBoundsIfSupported era
<*> validateTxFee sbe (Just fixedFee)
<*> pure TxValidityNoLowerBound
<*> pure (defaultTxValidityUpperBound sbe)
<*> pure TxMetadataNone
<*> pure TxAuxScriptsNone
<*> pure TxExtraKeyWitnessesNone
Expand All @@ -66,10 +67,10 @@ txBuild sbe (txin, txout) addressOrOutputs certs minting (Fee fixedFee) = do
<*> pure TxUpdateProposalNone
<*> pure minting
<*> pure TxScriptValidityNone
<*> pure TxGovernanceActionsNone
<*> pure TxVotesNone
<*> pure Nothing
<*> pure Nothing

case createAndValidateTransactionBody txBodyContent of
case createAndValidateTransactionBody sbe txBodyContent of
Left err -> left $ FaucetWebErrorTodo $ show err
Right txbody -> pure txbody
{-
Expand Down Expand Up @@ -114,17 +115,18 @@ txBuild sbe (txin, txout) addressOrOutputs certs minting (Fee fixedFee) = do
return balancedTxBody
-}

txSign :: IsShelleyBasedEra era
=> TxBody era
txSign :: ()
=> ShelleyBasedEra era
-> TxBody era
-> [ShelleyWitnessSigningKey]
-> Tx era
txSign txBody sks = tx
txSign era txBody sks = tx
--let (sksByron, sksShelley) = partitionSomeWitnesses $ map categoriseSomeWitness sks
where
shelleyKeyWitnesses = map (makeShelleyKeyWitness txBody) sks
shelleyKeyWitnesses = map (makeShelleyKeyWitness era txBody) sks
tx = makeSignedTransaction shelleyKeyWitnesses txBody

makeAndSignTx :: IsShelleyBasedEra era
makeAndSignTx :: ()
=> ShelleyBasedEra era
-> (TxIn, TxOut CtxUTxO era)
-> Either AddressAny [TxOutAnyEra]
Expand All @@ -140,5 +142,5 @@ makeAndSignTx sbe txinout addressOrOutputs skeys certs minting fee = do
let
txid :: TxId
txid = getTxId unsignedTx
signedTx = txSign unsignedTx skeys
signedTx = txSign sbe unsignedTx skeys
pure (signedTx, txid)
32 changes: 15 additions & 17 deletions cardano-faucet/src/Cardano/Faucet/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,11 +12,10 @@ import Prelude (fail)

import Cardano.Address.Derivation (Depth(RootK, AccountK, PaymentK, PolicyK), XPrv, genMasterKeyFromMnemonic, indexFromWord32, deriveAccountPrivateKey, deriveAddressPrivateKey, Index, DerivationType(Hardened, Soft))
import Cardano.Address.Style.Shelley (Shelley, Role(UTxOExternal, Stake), derivePolicyPrivateKey)
import Cardano.Api (AnyCardanoEra, IsCardanoEra, TxIn, TxOut, CtxUTxO, TxInMode, CardanoMode, TxId, FileError, Lovelace, AddressAny, AssetId(AssetId, AdaAssetId), Quantity, SigningKey, PaymentExtendedKey, VerificationKey, HashableScriptData)
import Cardano.Api (AnyCardanoEra, InputDecodeError, TxIn, TxOut, CtxUTxO, TxInMode, TxId, FileError, AddressAny, AssetId(AssetId, AdaAssetId), Quantity, SigningKey, PaymentExtendedKey, VerificationKey, HashableScriptData, docToText)
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (PoolId, StakeExtendedKey, StakeCredential, AssetName(..), NetworkId(Testnet, Mainnet), NetworkMagic(NetworkMagic), ShelleyWitnessSigningKey)
import Cardano.Api (InputDecodeError)
--import Cardano.CLI.Shelley.Run.Address (SomeAddressVerificationKey(AByronVerificationKey, APaymentVerificationKey, APaymentExtendedVerificationKey, AGenesisUTxOVerificationKey), ShelleyAddressCmdError, buildShelleyAddress)
--import Cardano.CLI.Shelley.Run.Transaction (ShelleyTxCmdError, renderShelleyTxCmdError)
import Cardano.CLI.Types.Errors.AddressCmdError
import Cardano.Mnemonic (mkSomeMnemonic, getMkSomeMnemonicError)
import Cardano.Prelude
import Control.Concurrent.STM (TMVar, TQueue)
Expand All @@ -35,7 +34,6 @@ import Data.Time.Clock (UTCTime, NominalDiffTime)
import Prelude (String, error, read)
import Servant (FromHttpApiData(parseHeader, parseQueryParam, parseUrlPiece))
import Web.Internal.FormUrlEncoded (ToForm(toForm), fromEntriesByKey)
import Cardano.CLI.Types.Errors.ShelleyAddressCmdError (ShelleyAddressCmdError)

-- the sitekey, secretkey, and token from recaptcha
newtype SiteKey = SiteKey { unSiteKey :: Text } deriving Show
Expand Down Expand Up @@ -63,7 +61,7 @@ data FaucetError = FaucetErrorSocketNotFound
| FaucetErrorConfigFileNotSet
| FaucetErrorBadMnemonic Text
| FaucetErrorBadIdx
| FaucetErrorShelleyAddr ShelleyAddressCmdError
| FaucetErrorAddr AddressCmdError
| FaucetErrorTodo2 Text
deriving Generic

Expand All @@ -74,7 +72,7 @@ renderFaucetError (FaucetErrorParsingConfig err) = show err
renderFaucetError FaucetErrorConfigFileNotSet = "$CONFIG_FILE not set"
renderFaucetError (FaucetErrorBadMnemonic msg) = "bad mnemonic " <> msg
renderFaucetError FaucetErrorBadIdx = "bad index"
renderFaucetError (FaucetErrorShelleyAddr err) = show err
renderFaucetError (FaucetErrorAddr err) = docToText $ renderAddressCmdError $ err
renderFaucetError (FaucetErrorTodo2 err) = show err

-- errors that can be sent to the user
Expand Down Expand Up @@ -104,11 +102,11 @@ instance Aeson.ToJSON FaucetWebError where
data ApiKey = Recaptcha Text | ApiKey Text deriving (Ord, Eq)

-- the state of the entire faucet
data IsCardanoEra era => FaucetState era = FaucetState
data FaucetState era = FaucetState
{ fsUtxoTMVar :: TMVar (Map TxIn (TxOut CtxUTxO era))
, fsStakeTMVar :: TMVar ([(Word32, SigningKey StakeExtendedKey, StakeCredential)], [(Word32, Lovelace, PoolId)])
, fsStakeTMVar :: TMVar ([(Word32, SigningKey StakeExtendedKey, StakeCredential)], [(Word32, L.Coin, PoolId)])
, fsNetwork :: NetworkId
, fsTxQueue :: TQueue (TxInMode CardanoMode, ByteString)
, fsTxQueue :: TQueue (TxInMode, ByteString)
, fsRootKey :: Shelley 'RootK XPrv
, fsPaymentSkey :: ShelleyWitnessSigningKey
, fsPaymentVkey :: VerificationKey PaymentExtendedKey
Expand Down Expand Up @@ -138,10 +136,10 @@ data SendMoneySent = SendMoneySent
, amount :: FaucetValue
}

data StakeKeyIntermediateState = StakeKeyIntermediateStateNotRegistered Word32 | StakeKeyIntermediateStateRegistered (Word32, SigningKey StakeExtendedKey, StakeCredential, Lovelace)
data StakeKeyIntermediateState = StakeKeyIntermediateStateNotRegistered Word32 | StakeKeyIntermediateStateRegistered (Word32, SigningKey StakeExtendedKey, StakeCredential, L.Coin)

data StakeKeyState = StakeKeyRegistered Word32 (SigningKey StakeExtendedKey) StakeCredential Lovelace
| StakeKeyDelegated Word32 Lovelace PoolId
data StakeKeyState = StakeKeyRegistered Word32 (SigningKey StakeExtendedKey) StakeCredential L.Coin
| StakeKeyDelegated Word32 L.Coin PoolId
| StakeKeyNotRegistered Word32 deriving Show

-- the full reply type for /send-money
Expand All @@ -163,7 +161,7 @@ instance Aeson.ToJSON DelegationReply where
-- a complete description of an api key
data ApiKeyValue = ApiKeyValue
{ akvApiKey :: Text
, akvLovelace :: Lovelace
, akvLovelace :: L.Coin
, akvRateLimit :: NominalDiffTime
, akvTokens :: Maybe FaucetToken
, akvCanDelegate :: Bool
Expand Down Expand Up @@ -220,9 +218,9 @@ instance Aeson.FromJSON FaucetConfigFile where

-- a value with only ada, or a value containing a mix of assets
-- TODO, maybe replace with the cardano Value type?
data FaucetValue = Ada Lovelace
| FaucetValueMultiAsset Lovelace FaucetToken
| FaucetValueManyTokens Lovelace deriving (Show, Eq, Ord)
data FaucetValue = Ada L.Coin
| FaucetValueMultiAsset L.Coin FaucetToken
| FaucetValueManyTokens L.Coin deriving (Show, Eq, Ord)

--tokenToValue :: FaucetToken -> Value
--tokenToValue (FaucetToken (AssetId policyid token, q)) = object [ "policyid" .= policyid, "token" .= token, "quantity" .= q ]
Expand Down
67 changes: 44 additions & 23 deletions cardano-faucet/src/Cardano/Faucet/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,22 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE GADTs #-}

module Cardano.Faucet.Utils where

import Cardano.Api (TxIn, TxOut(TxOut), CtxUTxO, Lovelace, CardanoEra, TxFee, txFeesExplicitInEra, TxFee(TxFeeImplicit, TxFeeExplicit), anyCardanoEra, TxValidityLowerBound(TxValidityNoLowerBound), TxValidityUpperBound(TxValidityNoUpperBound), validityNoUpperBoundSupportedInEra)
import Cardano.Api (TxIn, TxOut(TxOut), CtxUTxO, TxFee (..), defaultTxValidityUpperBound, TxValidityLowerBound(TxValidityNoLowerBound), TxValidityUpperBound, ShelleyBasedEra, shelleyBasedToCardanoEra, AnyCardanoEra (..), shelleyBasedEraConstraints, Tx, CardanoEra (..))
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (ShelleyBasedEra(..))
import qualified Cardano.CLI.Json.Friendly as CLI
import qualified Cardano.CLI.Types.MonadWarning as CLI
import Cardano.Faucet.Misc
import Cardano.Faucet.Types
import Cardano.Prelude hiding ((%))
import Control.Concurrent.STM (TMVar, takeTMVar, putTMVar)
import Control.Monad.Trans.Except.Extra (left)
import qualified Data.ByteString as BS
import Data.Map.Strict qualified as Map
import qualified Prelude

Expand Down Expand Up @@ -65,31 +72,45 @@ findUtxoOfSize utxoTMVar value = do
Just txinout -> pure txinout
Nothing -> throwSTM $ FaucetWebErrorUtxoNotFound value

validateTxFee ::
CardanoEra era
-> Maybe Lovelace
validateTxFee :: ()
=> ShelleyBasedEra era
-> Maybe L.Coin
-> ExceptT FaucetWebError IO (TxFee era)
validateTxFee era mfee = case (txFeesExplicitInEra era, mfee) of
(Left implicit, Nothing) -> return (TxFeeImplicit implicit)
(Right explicit, Just fee) -> return (TxFeeExplicit explicit fee)
(Right _, Nothing) -> txFeatureMismatch era
(Left _, Just _) -> txFeatureMismatch era
validateTxFee sbe mfee =
case mfee of
Nothing -> txFeatureMismatch sbe -- Fees are explicit since Shelley
Just fee -> return $ TxFeeExplicit sbe fee

txFeatureMismatch ::
CardanoEra era
txFeatureMismatch :: ()
=> ShelleyBasedEra era
-> ExceptT FaucetWebError IO a
txFeatureMismatch era = left (FaucetWebErrorFeatureMismatch (anyCardanoEra era))
txFeatureMismatch sbe =
left $ FaucetWebErrorFeatureMismatch $
shelleyBasedEraConstraints sbe AnyCardanoEra $ shelleyBasedToCardanoEra sbe

noBoundsIfSupported ::
CardanoEra era
-> ExceptT FaucetWebError IO (TxValidityLowerBound era, TxValidityUpperBound era)
noBoundsIfSupported era = (,)
<$> pure TxValidityNoLowerBound
<*> noUpperBoundIfSupported era
ShelleyBasedEra era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
noBoundsIfSupported sbe = (TxValidityNoLowerBound, defaultTxValidityUpperBound sbe)

noUpperBoundIfSupported ::
CardanoEra era
-> ExceptT FaucetWebError IO (TxValidityUpperBound era)
noUpperBoundIfSupported era = case validityNoUpperBoundSupportedInEra era of
Nothing -> txFeatureMismatch era
Just supported -> return (TxValidityNoUpperBound supported)
prettyFriendlyTx :: ()
=> ShelleyBasedEra era
-> Tx era
-> BS.ByteString
prettyFriendlyTx sbe tx =
CLI.friendlyBS CLI.FriendlyJson prettyTxAeson
where
era = shelleyBasedToCardanoEra sbe
prettyTxAeson = fst $ runState (CLI.runWarningStateT $ CLI.friendlyTxImpl era tx) []

-- | @cardanoEraToShelleyBasedEra@ converts a 'CardanoEra' to a 'ShelleyBasedEra'
-- or returns an error message if the era is not Shelley based.
cardanoEraToShelleyBasedEra :: CardanoEra era -> Either Text (ShelleyBasedEra era)
cardanoEraToShelleyBasedEra = \case
ByronEra -> Left "Byron is not a Shelley based era"
ShelleyEra -> Right ShelleyBasedEraShelley
AllegraEra -> Right ShelleyBasedEraAllegra
MaryEra -> Right ShelleyBasedEraMary
AlonzoEra -> Right ShelleyBasedEraAlonzo
BabbageEra -> Right ShelleyBasedEraBabbage
ConwayEra -> Right ShelleyBasedEraConway

0 comments on commit 890d4d0

Please sign in to comment.