blockfrost-api-0.2.1.0: API definitions for blockfrost.io
Safe HaskellNone
LanguageHaskell2010

Blockfrost.Types.Cardano.Epochs

Description

Responses for Cardano epoch quries

Synopsis

Documentation

data EpochInfo Source #

Information about an epoch

Constructors

EpochInfo 

Fields

Instances

Instances details
Eq EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Show EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Generic EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Associated Types

type Rep EpochInfo :: Type -> Type #

ToJSON EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

FromJSON EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

ToSample EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

HasEpoch EpochInfo Epoch Source # 
Instance details

Defined in Blockfrost.Lens

HasTxCount EpochInfo Integer Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasOutput EpochInfo a Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasFees EpochInfo a Source # 
Instance details

Defined in Blockfrost.Lens

HasStartTime EpochInfo POSIXTime Source # 
Instance details

Defined in Blockfrost.Lens

HasLastBlockTime EpochInfo POSIXTime Source # 
Instance details

Defined in Blockfrost.Lens

HasFirstBlockTime EpochInfo POSIXTime Source # 
Instance details

Defined in Blockfrost.Lens

HasEndTime EpochInfo POSIXTime Source # 
Instance details

Defined in Blockfrost.Lens

HasBlockCount EpochInfo Integer Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Maybe Lovelaces => HasActiveStake EpochInfo a Source # 
Instance details

Defined in Blockfrost.Lens

type Rep EpochInfo Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

type Rep EpochInfo = D1 ('MetaData "EpochInfo" "Blockfrost.Types.Cardano.Epochs" "blockfrost-api-0.2.1.0-KZcfvGT2yF56UZeMbClPE7" 'False) (C1 ('MetaCons "EpochInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_epochInfoEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Epoch) :*: S1 ('MetaSel ('Just "_epochInfoStartTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)) :*: (S1 ('MetaSel ('Just "_epochInfoEndTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime) :*: (S1 ('MetaSel ('Just "_epochInfoFirstBlockTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime) :*: S1 ('MetaSel ('Just "_epochInfoLastBlockTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))) :*: ((S1 ('MetaSel ('Just "_epochInfoBlockCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_epochInfoTxCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "_epochInfoOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces) :*: (S1 ('MetaSel ('Just "_epochInfoFees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces) :*: S1 ('MetaSel ('Just "_epochInfoActiveStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Lovelaces)))))))

data PoolStakeDistribution Source #

Stake distribution for an epoch for specific pool

Constructors

PoolStakeDistribution 

Fields

Instances

Instances details
Eq PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Show PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Generic PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Associated Types

type Rep PoolStakeDistribution :: Type -> Type #

ToJSON PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

FromJSON PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

ToSample PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

HasStakeAddress PoolStakeDistribution Address Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasAmount PoolStakeDistribution a Source # 
Instance details

Defined in Blockfrost.Lens

type Rep PoolStakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

type Rep PoolStakeDistribution = D1 ('MetaData "PoolStakeDistribution" "Blockfrost.Types.Cardano.Epochs" "blockfrost-api-0.2.1.0-KZcfvGT2yF56UZeMbClPE7" 'False) (C1 ('MetaCons "PoolStakeDistribution" 'PrefixI 'True) (S1 ('MetaSel ('Just "_poolStakeDistributionStakeAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address) :*: S1 ('MetaSel ('Just "_poolStakeDistributionAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces)))

data ProtocolParams Source #

Protocol parameters

Constructors

ProtocolParams 

Fields

Instances

Instances details
Eq ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Show ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Generic ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Associated Types

type Rep ProtocolParams :: Type -> Type #

ToJSON ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

FromJSON ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

ToSample ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

HasEpoch ProtocolParams Epoch Source # 
Instance details

Defined in Blockfrost.Lens

HasTau ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

HasRho ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

HasProtocolMinorVer ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasProtocolMajorVer ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasPriceStep ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

HasPriceMem ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasPoolDeposit ProtocolParams a Source # 
Instance details

Defined in Blockfrost.Lens

HasNonce ProtocolParams Text Source # 
Instance details

Defined in Blockfrost.Lens

HasNOpt ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasMinUtxo ProtocolParams a Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasMinPoolCost ProtocolParams a Source # 
Instance details

Defined in Blockfrost.Lens

HasMinFeeB ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMinFeeA ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxValSize ProtocolParams Quantity Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxTxSize ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxTxExSteps ProtocolParams Quantity Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxTxExMem ProtocolParams Quantity Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxCollateralInputs ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxBlockSize ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxBlockHeaderSize ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxBlockExSteps ProtocolParams Quantity Source # 
Instance details

Defined in Blockfrost.Lens

HasMaxBlockExMem ProtocolParams Quantity Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasKeyDeposit ProtocolParams a Source # 
Instance details

Defined in Blockfrost.Lens

HasEMax ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

HasDecentralisationParam ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

HasCollateralPercent ProtocolParams Integer Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasCoinsPerUtxoWord ProtocolParams a Source # 
Instance details

Defined in Blockfrost.Lens

HasA0 ProtocolParams Double Source # 
Instance details

Defined in Blockfrost.Lens

HasExtraEntropy ProtocolParams (Maybe Value) Source # 
Instance details

Defined in Blockfrost.Lens

type Rep ProtocolParams Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

type Rep ProtocolParams = D1 ('MetaData "ProtocolParams" "Blockfrost.Types.Cardano.Epochs" "blockfrost-api-0.2.1.0-KZcfvGT2yF56UZeMbClPE7" 'False) (C1 ('MetaCons "ProtocolParams" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "_protocolParamsEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Epoch) :*: (S1 ('MetaSel ('Just "_protocolParamsMinFeeA") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsMinFeeB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) :*: ((S1 ('MetaSel ('Just "_protocolParamsMaxBlockSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsMaxTxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "_protocolParamsMaxBlockHeaderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsKeyDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces)))) :*: (((S1 ('MetaSel ('Just "_protocolParamsPoolDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces) :*: S1 ('MetaSel ('Just "_protocolParamsEMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "_protocolParamsNOpt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsA0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :*: ((S1 ('MetaSel ('Just "_protocolParamsRho") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "_protocolParamsTau") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "_protocolParamsDecentralisationParam") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "_protocolParamsExtraEntropy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)))))) :*: (((S1 ('MetaSel ('Just "_protocolParamsProtocolMajorVer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: (S1 ('MetaSel ('Just "_protocolParamsProtocolMinorVer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsMinUtxo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces))) :*: ((S1 ('MetaSel ('Just "_protocolParamsMinPoolCost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces) :*: S1 ('MetaSel ('Just "_protocolParamsNonce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "_protocolParamsPriceMem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "_protocolParamsPriceStep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :*: (((S1 ('MetaSel ('Just "_protocolParamsMaxTxExMem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity) :*: S1 ('MetaSel ('Just "_protocolParamsMaxTxExSteps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity)) :*: (S1 ('MetaSel ('Just "_protocolParamsMaxBlockExMem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity) :*: S1 ('MetaSel ('Just "_protocolParamsMaxBlockExSteps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity))) :*: ((S1 ('MetaSel ('Just "_protocolParamsMaxValSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity) :*: S1 ('MetaSel ('Just "_protocolParamsCollateralPercent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "_protocolParamsMaxCollateralInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "_protocolParamsCoinsPerUtxoWord") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces)))))))

data StakeDistribution Source #

Active stake distribution for an epoch

Constructors

StakeDistribution 

Fields

Instances

Instances details
Eq StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Show StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Generic StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

Associated Types

type Rep StakeDistribution :: Type -> Type #

ToJSON StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

FromJSON StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

ToSample StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

HasStakeAddress StakeDistribution Address Source # 
Instance details

Defined in Blockfrost.Lens

HasPoolId StakeDistribution PoolId Source # 
Instance details

Defined in Blockfrost.Lens

a ~ Lovelaces => HasAmount StakeDistribution a Source # 
Instance details

Defined in Blockfrost.Lens

type Rep StakeDistribution Source # 
Instance details

Defined in Blockfrost.Types.Cardano.Epochs

type Rep StakeDistribution = D1 ('MetaData "StakeDistribution" "Blockfrost.Types.Cardano.Epochs" "blockfrost-api-0.2.1.0-KZcfvGT2yF56UZeMbClPE7" 'False) (C1 ('MetaCons "StakeDistribution" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stakeDistributionStakeAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address) :*: (S1 ('MetaSel ('Just "_stakeDistributionPoolId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolId) :*: S1 ('MetaSel ('Just "_stakeDistributionAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lovelaces))))