Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Polysemy.Blockfrost.Types
Synopsis
- data Blockfrost m a where
- GetRoot :: Blockfrost m (Either BlockfrostError URLVersion)
- GetHealth :: Blockfrost m (Either BlockfrostError Healthy)
- GetClock :: Blockfrost m (Either BlockfrostError ServerTime)
- GetMetrics :: Blockfrost m (Either BlockfrostError [Metric])
- GetMetricsEndpoints :: Blockfrost m (Either BlockfrostError [(Text, Metric)])
- NutlinkListAddress :: Address -> Blockfrost m (Either BlockfrostError NutlinkAddress)
- NutlinkListAddressTickers' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [NutlinkAddressTicker])
- NutlinkListAddressTickers :: Address -> Blockfrost m (Either BlockfrostError [NutlinkAddressTicker])
- NutlinkAddressTickers' :: Address -> Text -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [NutlinkTicker])
- NutlinkAddressTickers :: Address -> Text -> Blockfrost m (Either BlockfrostError [NutlinkTicker])
- NutlinkTickers' :: Text -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [(Address, NutlinkTicker)])
- NutlinkTickers :: Text -> Blockfrost m (Either BlockfrostError [(Address, NutlinkTicker)])
- IpfsGateway :: Text -> Blockfrost m (Either BlockfrostError IPFSData)
- IpfsPin :: Text -> Blockfrost m (Either BlockfrostError IPFSPinChange)
- IpfsListPins' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [IPFSPin])
- IpfsListPins :: Blockfrost m (Either BlockfrostError [IPFSPin])
- IpfsGetPin :: Text -> Blockfrost m (Either BlockfrostError IPFSPin)
- IpfsRemovePin :: Text -> Blockfrost m (Either BlockfrostError IPFSPinChange)
- GetLatestBlock :: Blockfrost m (Either BlockfrostError Block)
- GetLatestBlockTxs' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [TxHash])
- GetLatestBlockTxs :: Blockfrost m (Either BlockfrostError [TxHash])
- GetBlock :: Either Integer BlockHash -> Blockfrost m (Either BlockfrostError Block)
- GetBlockSlot :: Slot -> Blockfrost m (Either BlockfrostError Block)
- GetBlockEpochSlot :: Epoch -> Slot -> Blockfrost m (Either BlockfrostError Block)
- GetNextBlocks' :: Either Integer BlockHash -> Paged -> Blockfrost m (Either BlockfrostError [Block])
- GetNextBlocks :: Either Integer BlockHash -> Blockfrost m (Either BlockfrostError [Block])
- GetPreviousBlocks' :: Either Integer BlockHash -> Paged -> Blockfrost m (Either BlockfrostError [Block])
- GetPreviousBlocks :: Either Integer BlockHash -> Blockfrost m (Either BlockfrostError [Block])
- GetBlockTxs' :: Either Integer BlockHash -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [TxHash])
- GetBlockTxs :: Either Integer BlockHash -> Blockfrost m (Either BlockfrostError [TxHash])
- GetBlockAffectedAddresses' :: Either Integer BlockHash -> Paged -> Blockfrost m (Either BlockfrostError [(Address, [TxHash])])
- GetBlockAffectedAddresses :: Either Integer BlockHash -> Blockfrost m (Either BlockfrostError [(Address, [TxHash])])
- GetNetworkInfo :: Blockfrost m (Either BlockfrostError Network)
- GetNetworkEras :: Blockfrost m (Either BlockfrostError [NetworkEraSummary])
- GetAddressInfo :: Address -> Blockfrost m (Either BlockfrostError AddressInfo)
- GetAddressInfoExtended :: Address -> Blockfrost m (Either BlockfrostError AddressInfoExtended)
- GetAddressDetails :: Address -> Blockfrost m (Either BlockfrostError AddressDetails)
- GetAddressUtxos' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AddressUtxo])
- GetAddressUtxos :: Address -> Blockfrost m (Either BlockfrostError [AddressUtxo])
- GetAddressUtxosAsset' :: Address -> AssetId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AddressUtxo])
- GetAddressUtxosAsset :: Address -> AssetId -> Blockfrost m (Either BlockfrostError [AddressUtxo])
- GetAddressTransactions' :: Address -> Paged -> SortOrder -> Maybe BlockIndex -> Maybe BlockIndex -> Blockfrost m (Either BlockfrostError [AddressTransaction])
- GetAddressTransactions :: Address -> Blockfrost m (Either BlockfrostError [AddressTransaction])
- GetAssets' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AssetInfo])
- GetAssets :: Blockfrost m (Either BlockfrostError [AssetInfo])
- GetAssetDetails :: AssetId -> Blockfrost m (Either BlockfrostError AssetDetails)
- GetAssetHistory' :: AssetId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AssetHistory])
- GetAssetHistory :: AssetId -> Blockfrost m (Either BlockfrostError [AssetHistory])
- GetAssetTransactions' :: AssetId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AssetTransaction])
- GetAssetTransactions :: AssetId -> Blockfrost m (Either BlockfrostError [AssetTransaction])
- GetAssetAddresses' :: AssetId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AssetAddress])
- GetAssetAddresses :: AssetId -> Blockfrost m (Either BlockfrostError [AssetAddress])
- GetAssetsByPolicy' :: PolicyId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AssetInfo])
- GetAssetsByPolicy :: PolicyId -> Blockfrost m (Either BlockfrostError [AssetInfo])
- ListScripts' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError ScriptHashList)
- ListScripts :: Blockfrost m (Either BlockfrostError ScriptHashList)
- GetScript :: ScriptHash -> Blockfrost m (Either BlockfrostError Script)
- GetScriptRedeemers' :: ScriptHash -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [ScriptRedeemer])
- GetScriptRedeemers :: ScriptHash -> Blockfrost m (Either BlockfrostError [ScriptRedeemer])
- GetScriptDatum :: DatumHash -> Blockfrost m (Either BlockfrostError ScriptDatum)
- GetScriptDatumCBOR :: DatumHash -> Blockfrost m (Either BlockfrostError ScriptDatumCBOR)
- GetScriptJSON :: ScriptHash -> Blockfrost m (Either BlockfrostError ScriptJSON)
- GetScriptCBOR :: ScriptHash -> Blockfrost m (Either BlockfrostError ScriptCBOR)
- GetLatestEpoch :: Blockfrost m (Either BlockfrostError EpochInfo)
- GetLatestEpochProtocolParams :: Blockfrost m (Either BlockfrostError ProtocolParams)
- GetEpoch :: Epoch -> Blockfrost m (Either BlockfrostError EpochInfo)
- GetNextEpochs' :: Epoch -> Paged -> Blockfrost m (Either BlockfrostError [EpochInfo])
- GetNextEpochs :: Epoch -> Blockfrost m (Either BlockfrostError [EpochInfo])
- GetPreviousEpochs' :: Epoch -> Paged -> Blockfrost m (Either BlockfrostError [EpochInfo])
- GetPreviousEpochs :: Epoch -> Blockfrost m (Either BlockfrostError [EpochInfo])
- GetEpochStake' :: Epoch -> Paged -> Blockfrost m (Either BlockfrostError [StakeDistribution])
- GetEpochStake :: Epoch -> Blockfrost m (Either BlockfrostError [StakeDistribution])
- GetEpochStakeByPool' :: Epoch -> PoolId -> Paged -> Blockfrost m (Either BlockfrostError [PoolStakeDistribution])
- GetEpochStakeByPool :: Epoch -> PoolId -> Blockfrost m (Either BlockfrostError [PoolStakeDistribution])
- GetEpochBlocks' :: Epoch -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetEpochBlocks :: Epoch -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetEpochBlocksByPool' :: Epoch -> PoolId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetEpochBlocksByPool :: Epoch -> PoolId -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetEpochProtocolParams :: Epoch -> Blockfrost m (Either BlockfrostError ProtocolParams)
- GetTx :: TxHash -> Blockfrost m (Either BlockfrostError Transaction)
- GetTxUtxos :: TxHash -> Blockfrost m (Either BlockfrostError TransactionUtxos)
- GetTxRedeemers :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionRedeemer])
- GetTxStakes :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionStake])
- GetTxDelegations :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionDelegation])
- GetTxWithdrawals :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionWithdrawal])
- GetTxMirs :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionMir])
- GetTxPoolUpdates :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionPoolUpdate])
- GetTxPoolRetiring :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionPoolRetiring])
- GetTxMetadataJSON :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionMetaJSON])
- GetTxMetadataCBOR :: TxHash -> Blockfrost m (Either BlockfrostError [TransactionMetaCBOR])
- SubmitTx :: CBORString -> Blockfrost m (Either BlockfrostError TxHash)
- GetLedgerGenesis :: Blockfrost m (Either BlockfrostError Genesis)
- GetAccount :: Address -> Blockfrost m (Either BlockfrostError AccountInfo)
- GetAccountRewards' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountReward])
- GetAccountRewards :: Address -> Blockfrost m (Either BlockfrostError [AccountReward])
- GetAccountHistory' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountHistory])
- GetAccountHistory :: Address -> Blockfrost m (Either BlockfrostError [AccountHistory])
- GetAccountDelegations' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountDelegation])
- GetAccountDelegations :: Address -> Blockfrost m (Either BlockfrostError [AccountDelegation])
- GetAccountRegistrations' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountRegistration])
- GetAccountRegistrations :: Address -> Blockfrost m (Either BlockfrostError [AccountRegistration])
- GetAccountWithdrawals' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountWithdrawal])
- GetAccountWithdrawals :: Address -> Blockfrost m (Either BlockfrostError [AccountWithdrawal])
- GetAccountMirs' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AccountMir])
- GetAccountMirs :: Address -> Blockfrost m (Either BlockfrostError [AccountMir])
- GetAccountAssociatedAddresses' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [AddressAssociated])
- GetAccountAssociatedAddresses :: Address -> Blockfrost m (Either BlockfrostError [AddressAssociated])
- GetAccountAssociatedAddressesTotal :: Address -> Blockfrost m (Either BlockfrostError AddressAssociatedTotal)
- GetAccountAssociatedAssets' :: Address -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [Amount])
- GetAccountAssociatedAssets :: Address -> Blockfrost m (Either BlockfrostError [Amount])
- ListPools' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolId])
- ListPools :: Blockfrost m (Either BlockfrostError [PoolId])
- ListPoolsExtended' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [Pool])
- ListPoolsExtended :: Blockfrost m (Either BlockfrostError [Pool])
- ListRetiredPools' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolEpoch])
- ListRetiredPools :: Blockfrost m (Either BlockfrostError [PoolEpoch])
- ListRetiringPools' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolEpoch])
- ListRetiringPools :: Blockfrost m (Either BlockfrostError [PoolEpoch])
- GetPool :: PoolId -> Blockfrost m (Either BlockfrostError PoolInfo)
- GetPoolHistory' :: PoolId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolHistory])
- GetPoolHistory :: PoolId -> Blockfrost m (Either BlockfrostError [PoolHistory])
- GetPoolMetadata :: PoolId -> Blockfrost m (Either BlockfrostError (Maybe PoolMetadata))
- GetPoolRelays :: PoolId -> Blockfrost m (Either BlockfrostError [PoolRelay])
- GetPoolDelegators' :: PoolId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolDelegator])
- GetPoolDelegators :: PoolId -> Blockfrost m (Either BlockfrostError [PoolDelegator])
- GetPoolBlocks' :: PoolId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetPoolBlocks :: PoolId -> Blockfrost m (Either BlockfrostError [BlockHash])
- GetPoolUpdates' :: PoolId -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [PoolUpdate])
- GetPoolUpdates :: PoolId -> Blockfrost m (Either BlockfrostError [PoolUpdate])
- GetTxMetadataLabels' :: Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [TxMeta])
- GetTxMetadataLabels :: Blockfrost m (Either BlockfrostError [TxMeta])
- GetTxMetadataByLabelJSON' :: Text -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [TxMetaJSON])
- GetTxMetadataByLabelJSON :: Text -> Blockfrost m (Either BlockfrostError [TxMetaJSON])
- GetTxMetadataByLabelCBOR' :: Text -> Paged -> SortOrder -> Blockfrost m (Either BlockfrostError [TxMetaCBOR])
- GetTxMetadataByLabelCBOR :: Text -> Blockfrost m (Either BlockfrostError [TxMetaCBOR])
- data AccountDelegation = AccountDelegation Epoch TxHash Lovelaces PoolId
- data AccountHistory = AccountHistory Integer Lovelaces PoolId
- data AccountInfo = AccountInfo Address Bool (Maybe Integer) Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces (Maybe PoolId)
- data AccountMir = AccountMir Lovelaces TxHash
- data AccountRegistration = AccountRegistration AccountRegistrationAction TxHash
- data AccountRegistrationAction
- data AccountReward = AccountReward Epoch Lovelaces PoolId RewardType
- data AccountWithdrawal = AccountWithdrawal Lovelaces TxHash
- newtype Address = Address Text
- newtype AddressAssociated = AddressAssociated Address
- data AddressAssociatedTotal = AddressAssociatedTotal Address [Amount] [Amount] Integer
- data AddressDetails = AddressDetails Address [Amount] [Amount] Integer
- data AddressInfo = AddressInfo Address [Amount] (Maybe Address) AddressType Bool
- data AddressInfoExtended = AddressInfoExtended Address [AmountExtended] (Maybe Address) AddressType Bool
- data AddressTransaction = AddressTransaction TxHash Integer Integer POSIXTime
- data AddressType
- data AddressUtxo = AddressUtxo Address TxHash Integer [Amount] BlockHash (Maybe DatumHash) (Maybe InlineDatum) (Maybe ScriptHash)
- data Amount
- data AssetAction
- data AssetAddress = AssetAddress Address Quantity
- data AssetDetails = AssetDetails Text PolicyId (Maybe Text) Text Quantity TxHash Integer (Maybe Value) (Maybe AssetOnChainMetadata) (Maybe AssetMetadata) (Maybe Text)
- data AssetHistory = AssetHistory TxHash Quantity AssetAction
- newtype AssetId = AssetId Text
- data AssetInfo = AssetInfo Text Quantity
- data AssetMetadata = AssetMetadata Text Text (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Int)
- data AssetOnChainMetadata = AssetOnChainMetadata (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe [MetadataMediaFile])
- data AssetTransaction = AssetTransaction TxHash Integer Integer POSIXTime
- data Block = Block POSIXTime (Maybe Integer) BlockHash (Maybe Slot) (Maybe Epoch) (Maybe Integer) Text Integer Integer (Maybe Lovelaces) (Maybe Lovelaces) (Maybe Text) (Maybe Text) (Maybe Quantity) (Maybe BlockHash) (Maybe BlockHash) Integer
- data BlockfrostError
- newtype BlockHash = BlockHash Text
- newtype CBORString = CBORString ByteString
- newtype CostModels = CostModels (Map ScriptType (Map Text Integer))
- newtype DatumHash = DatumHash Text
- data DerivedAddress = DerivedAddress Text Integer Integer Text
- newtype Epoch = Epoch Integer
- data EpochInfo = EpochInfo Epoch POSIXTime POSIXTime POSIXTime POSIXTime Integer Integer Lovelaces Lovelaces (Maybe Lovelaces)
- newtype EpochLength = EpochLength Word64
- data Genesis = Genesis Rational Integer Lovelaces Integer Integer POSIXTime Integer Integer Integer Integer
- newtype Healthy = Healthy Bool
- newtype InlineDatum = InlineDatum ScriptDatumCBOR
- data IPFSAdd = IPFSAdd Text Text Quantity
- newtype IPFSData = IPFSData ByteString
- data IPFSPin = IPFSPin POSIXTime POSIXTime Text Quantity PinState
- data IPFSPinChange = IPFSPinChange Text PinState
- type Lovelaces = Discrete "ADA" "lovelace"
- data MetadataMediaFile = MetadataMediaFile (Maybe Text) (Maybe Text) (Maybe Text)
- data Metric = Metric POSIXTime Integer
- data Network = Network NetworkSupply NetworkStake
- data NetworkEraBound = NetworkEraBound Epoch Slot NominalDiffTime
- data NetworkEraParameters = NetworkEraParameters EpochLength NominalDiffTime Word64
- data NetworkEraSummary = NetworkEraSummary NetworkEraBound NetworkEraBound NetworkEraParameters
- data NetworkStake = NetworkStake Lovelaces Lovelaces
- data NetworkSupply = NetworkSupply Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces
- data NutlinkAddress = NutlinkAddress Address Text Text (Maybe Value)
- data NutlinkAddressTicker = NutlinkAddressTicker Text Integer Integer
- data NutlinkTicker = NutlinkTicker TxHash Integer Integer Value
- data Paged = Paged Int Int
- data PinState
- newtype PolicyId = PolicyId Text
- data Pool = Pool PoolId Text Lovelaces Lovelaces
- data PoolDelegator = PoolDelegator Text Lovelaces
- data PoolEpoch = PoolEpoch PoolId Epoch
- data PoolHistory = PoolHistory Epoch Integer Lovelaces Double Integer Lovelaces Lovelaces
- newtype PoolId = PoolId Text
- data PoolInfo = PoolInfo PoolId Text Text Integer Integer Lovelaces Double Double Double Lovelaces Double Lovelaces Lovelaces Rational Lovelaces Address [Address] [Text] [Text]
- data PoolMetadata = PoolMetadata PoolId Text (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text)
- data PoolRegistrationAction
- data PoolRelay = PoolRelay (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) Integer
- data PoolStakeDistribution = PoolStakeDistribution Address Lovelaces
- data PoolUpdate = PoolUpdate TxHash Integer PoolRegistrationAction
- data PoolUpdateMetadata = PoolUpdateMetadata (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text)
- data POSIXMillis
- data Pot
- data Project = Project Env Text
- data ProtocolParams = ProtocolParams Epoch Integer Integer Integer Integer Integer Lovelaces Lovelaces Integer Integer Rational Rational Rational Rational (Maybe Text) Integer Integer Lovelaces Lovelaces Text CostModels Rational Rational Quantity Quantity Quantity Quantity Quantity Integer Integer Lovelaces Lovelaces
- newtype Quantity = Quantity Integer
- data RewardType
- data Script = Script ScriptHash ScriptType (Maybe Integer)
- newtype ScriptCBOR = ScriptCBOR (Maybe Text)
- newtype ScriptDatum = ScriptDatum Value
- newtype ScriptDatumCBOR = ScriptDatumCBOR Text
- newtype ScriptHash = ScriptHash Text
- newtype ScriptHashList = ScriptHashList [ScriptHash]
- newtype ScriptJSON = ScriptJSON (Maybe Value)
- data ScriptRedeemer = ScriptRedeemer TxHash Integer ValidationPurpose DatumHash DatumHash Quantity Quantity Lovelaces
- data ScriptType
- newtype ServerTime = ServerTime POSIXTime
- newtype Slot = Slot Integer
- data SortOrder
- data StakeDistribution = StakeDistribution Address PoolId Lovelaces
- data ToLower
- data Transaction = Transaction Text BlockHash Integer Slot Integer [Amount] Lovelaces Lovelaces Integer (Maybe Text) (Maybe Text) Integer Integer Integer Integer Integer Integer Integer Integer Integer Bool
- data TransactionDelegation = TransactionDelegation Integer Address PoolId Epoch
- data TransactionMetaCBOR = TransactionMetaCBOR Text (Maybe Text)
- data TransactionMetaJSON = TransactionMetaJSON Text (Maybe Value)
- data TransactionMir = TransactionMir Pot Integer Address Lovelaces
- data TransactionPoolRetiring = TransactionPoolRetiring Integer PoolId Epoch
- data TransactionPoolUpdate = TransactionPoolUpdate Integer PoolId Text Lovelaces Double Lovelaces Address [Address] (Maybe PoolUpdateMetadata) [PoolRelay] Epoch
- data TransactionRedeemer = TransactionRedeemer Integer ValidationPurpose ScriptHash DatumHash DatumHash Quantity Quantity Lovelaces
- data TransactionStake = TransactionStake Integer Address Bool
- data TransactionUtxos = TransactionUtxos TxHash [UtxoInput] [UtxoOutput]
- data TransactionWithdrawal = TransactionWithdrawal Address Lovelaces
- newtype TxEval = TxEval (Either TxEvalFailure (Map TxEvalValidator TxEvalBudget))
- data TxEvalBudget = TxEvalBudget Integer Integer
- data TxEvalInput = TxEvalInput CBORString Value
- newtype TxHash = TxHash Text
- data TxMeta = TxMeta Text (Maybe Text) Quantity
- data TxMetaCBOR = TxMetaCBOR TxHash (Maybe Text)
- data TxMetaJSON = TxMetaJSON TxHash (Maybe Value)
- data URLVersion = URLVersion Text Text
- data UtxoInput = UtxoInput Address [Amount] TxHash Integer Bool (Maybe DatumHash) (Maybe InlineDatum) (Maybe ScriptHash) Bool
- data UtxoOutput = UtxoOutput Address [Amount] (Maybe DatumHash) Integer Bool (Maybe InlineDatum) (Maybe ScriptHash)
- data ValidationPurpose
Documentation
data Blockfrost m a where Source #
Constructors
data AccountDelegation #
Account delegations and associated transaction IDs
Constructors
AccountDelegation Epoch TxHash Lovelaces PoolId |
Instances
data AccountHistory #
History of accounts stake delegation
Constructors
AccountHistory Integer Lovelaces PoolId |
Instances
data AccountInfo #
Information about an account, identified by its stake address
Constructors
AccountInfo Address Bool (Maybe Integer) Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces Lovelaces (Maybe PoolId) |
Instances
data AccountMir #
Account MIR (Move Instantaneous Reward)
Constructors
AccountMir Lovelaces TxHash |
Instances
data AccountRegistration #
Account (de)registration
Constructors
AccountRegistration AccountRegistrationAction TxHash |
Instances
data AccountRegistrationAction #
Registration action
Constructors
Registered | |
Deregistered |
Instances
data AccountReward #
Reward received by an account
Constructors
AccountReward Epoch Lovelaces PoolId RewardType |
Instances
data AccountWithdrawal #
Withdrawal from an account
Constructors
AccountWithdrawal Lovelaces TxHash |
Instances
Instances
newtype AddressAssociated #
Address associated with an account address
Constructors
AddressAssociated Address |
Instances
data AddressAssociatedTotal #
Detailed information about account associated addresses
Constructors
AddressAssociatedTotal Address [Amount] [Amount] Integer |
Instances
data AddressDetails #
Details about Cardano address
Constructors
AddressDetails Address [Amount] [Amount] Integer |
Instances
data AddressInfo #
Information about Cardano address
Constructors
AddressInfo Address [Amount] (Maybe Address) AddressType Bool |
Instances
data AddressInfoExtended #
Information about Cardano address
Constructors
AddressInfoExtended Address [AmountExtended] (Maybe Address) AddressType Bool |
Instances
data AddressTransaction #
Transactions on the address
Constructors
AddressTransaction TxHash Integer Integer POSIXTime |
Instances
data AddressType #
Type (era) of an address
Instances
data AddressUtxo #
UTxOs of the address
Constructors
AddressUtxo Address TxHash Integer [Amount] BlockHash (Maybe DatumHash) (Maybe InlineDatum) (Maybe ScriptHash) |
Instances
Amount, which is either `AdaAmount Lovelaces` representing amount of lovelaces or `AssetAmount SomeDiscrete` for asset amounts, identified by concatenation of asset policy ID and hex-encoded asset_name
Constructors
AdaAmount Lovelaces | |
AssetAmount SomeDiscrete |
Instances
data AssetAction #
Instances
FromJSON AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets | |
ToJSON AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetAction -> Value # toEncoding :: AssetAction -> Encoding # toJSONList :: [AssetAction] -> Value # toEncodingList :: [AssetAction] -> Encoding # omitField :: AssetAction -> Bool # | |
Generic AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets Associated Types type Rep AssetAction :: Type -> Type # | |
Show AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets Methods showsPrec :: Int -> AssetAction -> ShowS # show :: AssetAction -> String # showList :: [AssetAction] -> ShowS # | |
Eq AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets | |
ToSample AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets Methods toSamples :: Proxy AssetAction -> [(Text, AssetAction)] # | |
HasAction AssetHistory AssetAction | |
Defined in Blockfrost.Lens Methods | |
type Rep AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets |
data AssetAddress #
An address containing specific asset
Constructors
AssetAddress Address Quantity |
Instances
data AssetDetails #
Details of an asset
Constructors
AssetDetails Text PolicyId (Maybe Text) Text Quantity TxHash Integer (Maybe Value) (Maybe AssetOnChainMetadata) (Maybe AssetMetadata) (Maybe Text) |
Instances
data AssetHistory #
History of an asset
Constructors
AssetHistory TxHash Quantity AssetAction |
Instances
Concatenation of asset policy ID and hex-encoded asset name
Instances
FromJSON AssetId | |
Defined in Blockfrost.Types.Shared.AssetId | |
ToJSON AssetId | |
IsString AssetId | |
Defined in Blockfrost.Types.Shared.AssetId Methods fromString :: String -> AssetId # | |
Generic AssetId | |
Show AssetId | |
Eq AssetId | |
Ord AssetId | |
Defined in Blockfrost.Types.Shared.AssetId | |
FromHttpApiData AssetId | |
Defined in Blockfrost.Types.Shared.AssetId Methods parseUrlPiece :: Text -> Either Text AssetId # parseHeader :: ByteString -> Either Text AssetId # | |
ToHttpApiData AssetId | |
Defined in Blockfrost.Types.Shared.AssetId Methods toUrlPiece :: AssetId -> Text # toEncodedUrlPiece :: AssetId -> Builder # toHeader :: AssetId -> ByteString # toQueryParam :: AssetId -> Text # toEncodedQueryParam :: AssetId -> Builder # | |
ToSample AssetId | |
ToCapture (Capture "asset" AssetId) | |
Defined in Blockfrost.Types.Shared.AssetId | |
type Rep AssetId | |
Defined in Blockfrost.Types.Shared.AssetId |
Asset information, result of listing assets
Instances
FromJSON AssetInfo | |
Defined in Blockfrost.Types.Cardano.Assets | |
ToJSON AssetInfo | |
Generic AssetInfo | |
Show AssetInfo | |
Eq AssetInfo | |
ToSample AssetInfo | |
HasAsset AssetInfo Text | |
HasQuantity AssetInfo Quantity | |
type Rep AssetInfo | |
Defined in Blockfrost.Types.Cardano.Assets type Rep AssetInfo = D1 ('MetaData "AssetInfo" "Blockfrost.Types.Cardano.Assets" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "AssetInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_assetInfoAsset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_assetInfoQuantity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity))) |
data AssetMetadata #
Asset metadata obtained from Cardano token registry https://github.com/cardano-foundation/cardano-token-registry
Instances
data AssetOnChainMetadata #
On-chain metadata stored in the minting transaction under label 721, community discussion around the standard ongoing at https://github.com/cardano-foundation/CIPs/pull/85
Constructors
AssetOnChainMetadata (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe [MetadataMediaFile]) |
Instances
data AssetTransaction #
Transaction of an asset
Constructors
AssetTransaction TxHash Integer Integer POSIXTime |
Instances
Information about a block
Constructors
Block POSIXTime (Maybe Integer) BlockHash (Maybe Slot) (Maybe Epoch) (Maybe Integer) Text Integer Integer (Maybe Lovelaces) (Maybe Lovelaces) (Maybe Text) (Maybe Text) (Maybe Quantity) (Maybe BlockHash) (Maybe BlockHash) Integer |
Instances
data BlockfrostError #
Constructors
Instances
Show BlockfrostError | |
Defined in Blockfrost.Client.Core Methods showsPrec :: Int -> BlockfrostError -> ShowS # show :: BlockfrostError -> String # showList :: [BlockfrostError] -> ShowS # | |
Eq BlockfrostError | |
Defined in Blockfrost.Client.Core Methods (==) :: BlockfrostError -> BlockfrostError -> Bool # (/=) :: BlockfrostError -> BlockfrostError -> Bool # | |
Monad m => MonadError BlockfrostError (BlockfrostClientT m) | |
Defined in Blockfrost.Client.Types Methods throwError :: BlockfrostError -> BlockfrostClientT m a # catchError :: BlockfrostClientT m a -> (BlockfrostError -> BlockfrostClientT m a) -> BlockfrostClientT m a # |
Instances
newtype CBORString #
Wrapper for CBOR encoded ByteString
s
used for submitting a transaction
Constructors
CBORString ByteString |
Instances
newtype CostModels #
Constructors
CostModels (Map ScriptType (Map Text Integer)) |
Instances
Hash of the datum
Instances
data DerivedAddress #
Derived Shelley address
Constructors
DerivedAddress Text Integer Integer Text |
Instances
Instances
Information about an epoch
Constructors
EpochInfo Epoch POSIXTime POSIXTime POSIXTime POSIXTime Integer Integer Lovelaces Lovelaces (Maybe Lovelaces) |
Instances
newtype EpochLength #
Constructors
EpochLength Word64 |
Instances
Information about blockchain genesis
Constructors
Genesis Rational Integer Lovelaces Integer Integer POSIXTime Integer Integer Integer Integer |
Instances
Health endpoint reply
newtype InlineDatum #
Constructors
InlineDatum ScriptDatumCBOR |
Instances
IPFS Add response
Instances
FromJSON IPFSAdd | |
Defined in Blockfrost.Types.IPFS | |
ToJSON IPFSAdd | |
Generic IPFSAdd | |
Show IPFSAdd | |
Eq IPFSAdd | |
ToSample IPFSAdd | |
HasIpfsHash IPFSAdd Text | |
HasName IPFSAdd Text | |
HasSize IPFSAdd Quantity | |
type Rep IPFSAdd | |
Defined in Blockfrost.Types.IPFS type Rep IPFSAdd = D1 ('MetaData "IPFSAdd" "Blockfrost.Types.IPFS" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "IPFSAdd" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ipfsAddName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_ipfsAddIpfsHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_ipfsAddSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity)))) |
Constructors
IPFSData ByteString |
Instances
IPFS Pin information
Instances
data IPFSPinChange #
IPFS Pin Add response
Constructors
IPFSPinChange Text PinState |
Instances
data MetadataMediaFile #
Additional media files (accordingly to CIP25 and CIP68)
Instances
Metrics response
Instances
FromJSON Metric | |
Defined in Blockfrost.Types.Common | |
ToJSON Metric | |
Generic Metric | |
Show Metric | |
Eq Metric | |
ToSample Metric | |
FromJSON (Text, Metric) | |
ToJSON (Text, Metric) | |
ToSample (Text, Metric) | |
type Rep Metric | |
Defined in Blockfrost.Types.Common type Rep Metric = D1 ('MetaData "Metric" "Blockfrost.Types.Common" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "Metric" 'PrefixI 'True) (S1 ('MetaSel ('Just "_metricTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime) :*: S1 ('MetaSel ('Just "_metricCalls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) |
Detailed network information
Constructors
Network NetworkSupply NetworkStake |
Instances
FromJSON Network | |
Defined in Blockfrost.Types.Cardano.Network | |
ToJSON Network | |
Generic Network | |
Show Network | |
Eq Network | |
ToSample Network | |
HasStake Network NetworkStake | |
Defined in Blockfrost.Lens Methods | |
HasSupply Network NetworkSupply | |
Defined in Blockfrost.Lens Methods | |
type Rep Network | |
Defined in Blockfrost.Types.Cardano.Network type Rep Network = D1 ('MetaData "Network" "Blockfrost.Types.Cardano.Network" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "Network" 'PrefixI 'True) (S1 ('MetaSel ('Just "_networkSupply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NetworkSupply) :*: S1 ('MetaSel ('Just "_networkStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NetworkStake))) |
data NetworkEraBound #
Time bounds of an era.
Constructors
NetworkEraBound Epoch Slot NominalDiffTime |
Instances
data NetworkEraParameters #
Parameters for a network era which can vary between hardforks.
Constructors
NetworkEraParameters EpochLength NominalDiffTime Word64 |
Instances
data NetworkEraSummary #
Summary of information about network eras.
Instances
data NetworkStake #
Live and active stake of the whole network
Constructors
NetworkStake Lovelaces Lovelaces |
Instances
data NetworkSupply #
Lovelace supply data
Instances
data NutlinkAddress #
Specific address metadata
Instances
data NutlinkAddressTicker #
Ticker for specific metadata oracle
Constructors
NutlinkAddressTicker Text Integer Integer |
Instances
data NutlinkTicker #
Specific ticker record
Constructors
NutlinkTicker TxHash Integer Integer Value |
Instances
Pagination parameters
State of the pinned object,
which is Queued
when we are retriving object.
If this is successful the state is changed to Pinned
or Failed
if not.
The state Gc
means the pinned item has been garbage collected
due to account being over storage quota or after it has been
moved to Unpinned
state by removing the object pin.
Instances
FromJSON PinState | |
Defined in Blockfrost.Types.IPFS | |
ToJSON PinState | |
Generic PinState | |
Show PinState | |
Eq PinState | |
Ord PinState | |
Defined in Blockfrost.Types.IPFS | |
HasState IPFSPin PinState | |
HasState IPFSPinChange PinState | |
Defined in Blockfrost.Lens Methods | |
type Rep PinState | |
Defined in Blockfrost.Types.IPFS type Rep PinState = D1 ('MetaData "PinState" "Blockfrost.Types.IPFS" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) ((C1 ('MetaCons "Queued" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pinned" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Unpinned" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Failed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gc" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Minting policy Id
Instances
FromJSON PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId | |
ToJSON PolicyId | |
IsString PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId Methods fromString :: String -> PolicyId # | |
Generic PolicyId | |
Show PolicyId | |
Eq PolicyId | |
FromHttpApiData PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId Methods parseUrlPiece :: Text -> Either Text PolicyId # parseHeader :: ByteString -> Either Text PolicyId # | |
ToHttpApiData PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId Methods toUrlPiece :: PolicyId -> Text # toEncodedUrlPiece :: PolicyId -> Builder # toHeader :: PolicyId -> ByteString # toQueryParam :: PolicyId -> Text # toEncodedQueryParam :: PolicyId -> Builder # | |
ToSample PolicyId | |
HasPolicyId AssetDetails PolicyId | |
Defined in Blockfrost.Lens Methods | |
ToCapture (Capture "policy_id" PolicyId) | |
Defined in Blockfrost.Types.Shared.PolicyId | |
type Rep PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId |
Extended pool info
Instances
FromJSON Pool | |
Defined in Blockfrost.Types.Cardano.Pools | |
ToJSON Pool | |
Generic Pool | |
Show Pool | |
Eq Pool | |
ToSample Pool | |
a ~ Lovelaces => HasActiveStake Pool a | |
Defined in Blockfrost.Lens Methods activeStake :: Lens' Pool a # | |
HasHex Pool Text | |
a ~ Lovelaces => HasLiveStake Pool a | |
Defined in Blockfrost.Lens | |
HasPoolId Pool PoolId | |
type Rep Pool | |
Defined in Blockfrost.Types.Cardano.Pools type Rep Pool = D1 ('MetaData "Pool" "Blockfrost.Types.Cardano.Pools" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "Pool" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_poolPoolId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolId) :*: S1 ('MetaSel ('Just "_poolHex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "_poolActiveStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces) :*: S1 ('MetaSel ('Just "_poolLiveStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces)))) |
data PoolDelegator #
Stake pool delegator
Constructors
PoolDelegator Text Lovelaces |
Instances
Retirement epoch for pool
Instances
FromJSON PoolEpoch | |
Defined in Blockfrost.Types.Cardano.Pools | |
ToJSON PoolEpoch | |
Generic PoolEpoch | |
Show PoolEpoch | |
Eq PoolEpoch | |
ToSample PoolEpoch | |
HasEpoch PoolEpoch Epoch | |
HasPoolId PoolEpoch PoolId | |
type Rep PoolEpoch | |
Defined in Blockfrost.Types.Cardano.Pools type Rep PoolEpoch = D1 ('MetaData "PoolEpoch" "Blockfrost.Types.Cardano.Pools" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "PoolEpoch" 'PrefixI 'True) (S1 ('MetaSel ('Just "_poolEpochPoolId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolId) :*: S1 ('MetaSel ('Just "_poolEpochEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Epoch))) |
data PoolHistory #
History of a stake pool parameters over epochs
Instances
Instances
Detailed pool information
Constructors
PoolInfo PoolId Text Text Integer Integer Lovelaces Double Double Double Lovelaces Double Lovelaces Lovelaces Rational Lovelaces Address [Address] [Text] [Text] |
Instances
data PoolMetadata #
Stake pool registration metadata
Constructors
PoolMetadata PoolId Text (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) |
Instances
data PoolRegistrationAction #
Registration action of a pool
Constructors
PoolRegistered | |
PoolDeregistered |
Instances
Relays of a stake pool
Instances
data PoolStakeDistribution #
Stake distribution for an epoch for specific pool
Constructors
PoolStakeDistribution Address Lovelaces |
Instances
data PoolUpdate #
Certificate update to the stake pool
Constructors
PoolUpdate TxHash Integer PoolRegistrationAction |
Instances
data PoolUpdateMetadata #
Update of a pool metadata
Constructors
PoolUpdateMetadata (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) (Maybe Text) |
Instances
data POSIXMillis #
Instances
Pot from which MIRs are transferred
Instances
FromJSON Pot | |
Defined in Blockfrost.Types.Cardano.Transactions | |
ToJSON Pot | |
Generic Pot | |
Show Pot | |
Eq Pot | |
ToSample Pot | |
HasPot TransactionMir Pot | |
Defined in Blockfrost.Lens Methods pot :: Lens' TransactionMir Pot # | |
type Rep Pot | |
Defined in Blockfrost.Types.Cardano.Transactions |
Instances
IsString Project | |
Defined in Blockfrost.Auth Methods fromString :: String -> Project # | |
Generic Project | |
Show Project | |
Eq Project | |
Monad m => MonadReader ClientConfig (BlockfrostClientT m) | |
Defined in Blockfrost.Client.Types Methods ask :: BlockfrostClientT m ClientConfig # local :: (ClientConfig -> ClientConfig) -> BlockfrostClientT m a -> BlockfrostClientT m a # reader :: (ClientConfig -> a) -> BlockfrostClientT m a # | |
type Rep Project | |
Defined in Blockfrost.Auth type Rep Project = D1 ('MetaData "Project" "Blockfrost.Auth" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "Project" 'PrefixI 'True) (S1 ('MetaSel ('Just "projectEnv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Env) :*: S1 ('MetaSel ('Just "projectId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data ProtocolParams #
Protocol parameters
Constructors
Instances
Instances
data RewardType #
Reward type
Constructors
Leader | |
Member | |
PoolDepositRefund |
Instances
Script info
Constructors
Script ScriptHash ScriptType (Maybe Integer) |
Instances
FromJSON Script | |
Defined in Blockfrost.Types.Cardano.Scripts | |
ToJSON Script | |
Generic Script | |
Show Script | |
Eq Script | |
ToSample Script | |
type Rep Script | |
Defined in Blockfrost.Types.Cardano.Scripts type Rep Script = D1 ('MetaData "Script" "Blockfrost.Types.Cardano.Scripts" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "_scriptScriptHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptHash) :*: (S1 ('MetaSel ('Just "_scriptType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptType) :*: S1 ('MetaSel ('Just "_scriptSerialisedSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer))))) |
newtype ScriptCBOR #
Constructors
ScriptCBOR (Maybe Text) |
Instances
newtype ScriptDatum #
Constructors
ScriptDatum Value |
Instances
newtype ScriptDatumCBOR #
Constructors
ScriptDatumCBOR Text |
Instances
newtype ScriptHash #
Script Hash newtype
Constructors
ScriptHash Text |
Instances
newtype ScriptHashList #
Wrapper for list of ScriptHash-es, used by script list endpoint
Constructors
ScriptHashList [ScriptHash] |
Instances
newtype ScriptJSON #
Constructors
ScriptJSON (Maybe Value) |
Instances
data ScriptRedeemer #
Script redeemer
Constructors
ScriptRedeemer TxHash Integer ValidationPurpose DatumHash DatumHash Quantity Quantity Lovelaces |
Instances
data ScriptType #
Script type
Instances
newtype ServerTime #
Health clock endpoint reply
Constructors
ServerTime POSIXTime |
Instances
Instances
FromJSON Slot | |
Defined in Blockfrost.Types.Shared.Slot | |
ToJSON Slot | |
Enum Slot | |
Generic Slot | |
Num Slot | |
Integral Slot | |
Real Slot | |
Defined in Blockfrost.Types.Shared.Slot Methods toRational :: Slot -> Rational # | |
Show Slot | |
Eq Slot | |
Ord Slot | |
FromHttpApiData Slot | |
Defined in Blockfrost.Types.Shared.Slot | |
ToHttpApiData Slot | |
Defined in Blockfrost.Types.Shared.Slot Methods toUrlPiece :: Slot -> Text # toEncodedUrlPiece :: Slot -> Builder # toHeader :: Slot -> ByteString # toQueryParam :: Slot -> Text # toEncodedQueryParam :: Slot -> Builder # | |
ToSample Slot | |
HasBoundSlot NetworkEraBound Slot | |
Defined in Blockfrost.Lens Methods | |
HasSlot Transaction Slot | |
Defined in Blockfrost.Lens Methods slot :: Lens' Transaction Slot # | |
HasSlot Block (Maybe Slot) | |
ToCapture (Capture "slot_number" Slot) | |
Defined in Blockfrost.Types.Shared.Slot | |
type Rep Slot | |
Defined in Blockfrost.Types.Shared.Slot |
Constructors
Ascending | |
Descending |
Instances
Show SortOrder | |
Default SortOrder | |
Defined in Blockfrost.Util.Sorting | |
Eq SortOrder | |
Ord SortOrder | |
FromHttpApiData SortOrder | |
Defined in Blockfrost.Util.Sorting Methods parseUrlPiece :: Text -> Either Text SortOrder # parseHeader :: ByteString -> Either Text SortOrder # | |
ToHttpApiData SortOrder | |
Defined in Blockfrost.Util.Sorting Methods toUrlPiece :: SortOrder -> Text # toEncodedUrlPiece :: SortOrder -> Builder # toHeader :: SortOrder -> ByteString # toQueryParam :: SortOrder -> Text # toEncodedQueryParam :: SortOrder -> Builder # |
data StakeDistribution #
Active stake distribution for an epoch
Constructors
StakeDistribution Address PoolId Lovelaces |
Instances
Instances
StringModifier ToLower | |
Defined in Blockfrost.Types.Shared.Opts Methods getStringModifier :: String -> String # |
data Transaction #
Information about a transaction
Constructors
Transaction Text BlockHash Integer Slot Integer [Amount] Lovelaces Lovelaces Integer (Maybe Text) (Maybe Text) Integer Integer Integer Integer Integer Integer Integer Integer Integer Bool |
Instances
data TransactionDelegation #
Information about delegation certificates of a specific transaction
Constructors
TransactionDelegation Integer Address PoolId Epoch |
Instances
data TransactionMetaCBOR #
Transaction metadata in CBOR
Constructors
TransactionMetaCBOR Text (Maybe Text) |
Instances
data TransactionMetaJSON #
Transaction metadata in JSON
Constructors
TransactionMetaJSON Text (Maybe Value) |
Instances
data TransactionMir #
Information about Move Instantaneous Rewards (MIRs) of a specific transaction
Constructors
TransactionMir Pot Integer Address Lovelaces |
Instances
data TransactionPoolRetiring #
Information about stake pool retirements within a specific transaction
Constructors
TransactionPoolRetiring Integer PoolId Epoch |
Instances
data TransactionPoolUpdate #
Information about stake pool registration and update certificates of a specific transaction
Constructors
TransactionPoolUpdate Integer PoolId Text Lovelaces Double Lovelaces Address [Address] (Maybe PoolUpdateMetadata) [PoolRelay] Epoch |
Instances
data TransactionRedeemer #
Transaction redeemer
Constructors
TransactionRedeemer Integer ValidationPurpose ScriptHash DatumHash DatumHash Quantity Quantity Lovelaces |
Instances
data TransactionStake #
Information about (de-)registration of a stake address within a transaction
Constructors
TransactionStake Integer Address Bool |
Instances
data TransactionUtxos #
Transaction UTxOs
Constructors
TransactionUtxos TxHash [UtxoInput] [UtxoOutput] |
Instances
data TransactionWithdrawal #
Information about withdrawals of a specific transaction
Constructors
TransactionWithdrawal Address Lovelaces |
Instances
Transaction evaluation result wrapper
Constructors
TxEval (Either TxEvalFailure (Map TxEvalValidator TxEvalBudget)) |
Instances
FromJSON TxEval | |
Defined in Blockfrost.Types.Cardano.Utils | |
ToJSON TxEval | |
Generic TxEval | |
Show TxEval | |
Eq TxEval | |
ToSample TxEval | |
HasResult TxEval (Either TxEvalFailure (Map TxEvalValidator TxEvalBudget)) | |
Defined in Blockfrost.Lens Methods result :: Lens' TxEval (Either TxEvalFailure (Map TxEvalValidator TxEvalBudget)) # | |
type Rep TxEval | |
Defined in Blockfrost.Types.Cardano.Utils type Rep TxEval = D1 ('MetaData "TxEval" "Blockfrost.Types.Cardano.Utils" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'True) (C1 ('MetaCons "TxEval" 'PrefixI 'True) (S1 ('MetaSel ('Just "_txEvalResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either TxEvalFailure (Map TxEvalValidator TxEvalBudget))))) |
data TxEvalBudget #
Constructors
TxEvalBudget Integer Integer |
Instances
data TxEvalInput #
Transaction evaluation input for UTXO variant
Constructors
TxEvalInput CBORString Value |
Instances
Id (hash) of the transaction
Instances
Transaction metadata label in use
Instances
FromJSON TxMeta | |
Defined in Blockfrost.Types.Cardano.Metadata | |
ToJSON TxMeta | |
Generic TxMeta | |
Show TxMeta | |
Eq TxMeta | |
ToSample TxMeta | |
HasCount TxMeta Quantity | |
HasLabel TxMeta Text | |
HasCip10 TxMeta (Maybe Text) | |
type Rep TxMeta | |
Defined in Blockfrost.Types.Cardano.Metadata type Rep TxMeta = D1 ('MetaData "TxMeta" "Blockfrost.Types.Cardano.Metadata" "blockfrost-api-0.10.0.0-ErjKJ23z0xg5qL7d767ABF" 'False) (C1 ('MetaCons "TxMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "_txMetaLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_txMetaCip10") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_txMetaCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity)))) |
data TxMetaCBOR #
Transaction metadata content in CBOR
Constructors
TxMetaCBOR TxHash (Maybe Text) |
Instances
data TxMetaJSON #
Transaction metadata content in JSON
Constructors
TxMetaJSON TxHash (Maybe Value) |
Instances
data URLVersion #
Root endpoint reply
Constructors
URLVersion Text Text |
Instances
Transaction input UTxO
Constructors
UtxoInput Address [Amount] TxHash Integer Bool (Maybe DatumHash) (Maybe InlineDatum) (Maybe ScriptHash) Bool |
Instances
data UtxoOutput #
Transaction output UTxO
Constructors
UtxoOutput Address [Amount] (Maybe DatumHash) Integer Bool (Maybe InlineDatum) (Maybe ScriptHash) |
Instances
data ValidationPurpose #
Validation purpose