Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- addEpochInterval ∷ EpochNo → EpochInterval → EpochNo
- binOpEpochNo ∷ (Word64 → Word64 → Word64) → EpochNo → EpochNo → EpochNo
- newtype SlotNo = SlotNo {}
- data WithOrigin t
- newtype EpochNo = EpochNo {}
- newtype EpochSize = EpochSize {}
- newtype EpochInterval = EpochInterval {}
- newtype BlockNo = BlockNo {}
- data ProtVer = ProtVer {}
- module Cardano.Ledger.Binary.Version
- type FixedPoint = Digits34
- (==>) ∷ Bool → Bool → Bool
- (⭒) ∷ Nonce → Nonce → Nonce
- data Network
- networkToWord8 ∷ Network → Word8
- word8ToNetwork ∷ Word8 → Maybe Network
- data Nonce
- = Nonce !(Hash Blake2b_256 Nonce)
- | NeutralNonce
- newtype Seed = Seed (Hash Blake2b_256 Seed)
- data UnitInterval
- data PositiveUnitInterval
- data PositiveInterval
- data NonNegativeInterval
- class Bounded r ⇒ BoundedRational r where
- boundRational ∷ Rational → Maybe r
- unboundRational ∷ r → Rational
- fpPrecision ∷ FixedPoint
- integralToBounded ∷ ∀ i b m. (Integral i, Integral b, Bounded b, MonadFail m) ⇒ i → m b
- promoteRatio ∷ Integral a ⇒ Ratio a → Rational
- invalidKey ∷ MonadFail m ⇒ Word → m a
- mkNonceFromOutputVRF ∷ OutputVRF v → Nonce
- mkNonceFromNumber ∷ Word64 → Nonce
- data Url
- urlToText ∷ Url → Text
- textToUrl ∷ MonadFail m ⇒ Int → Text → m Url
- data DnsName
- dnsToText ∷ DnsName → Text
- textToDns ∷ MonadFail m ⇒ Int → Text → m DnsName
- newtype Port = Port {}
- data ActiveSlotCoeff
- mkActiveSlotCoeff ∷ PositiveUnitInterval → ActiveSlotCoeff
- activeSlotVal ∷ ActiveSlotCoeff → PositiveUnitInterval
- activeSlotLog ∷ ActiveSlotCoeff → FixedPoint
- module Data.Maybe.Strict
- newtype BlocksMade c = BlocksMade {
- unBlocksMade ∷ Map (KeyHash 'StakePool c) Natural
- kindObject ∷ Text → [Pair] → Value
- newtype TxIx = TxIx {}
- txIxToInt ∷ TxIx → Int
- txIxFromIntegral ∷ ∀ a m. (Integral a, MonadFail m) ⇒ a → m TxIx
- mkTxIx ∷ Word16 → TxIx
- mkTxIxPartial ∷ HasCallStack ⇒ Integer → TxIx
- newtype CertIx = CertIx {}
- certIxToInt ∷ CertIx → Int
- certIxFromIntegral ∷ ∀ a m. (Integral a, MonadFail m) ⇒ a → m CertIx
- mkCertIx ∷ Word16 → CertIx
- mkCertIxPartial ∷ HasCallStack ⇒ Integer → CertIx
- data Anchor c = Anchor {
- anchorUrl ∷ !Url
- anchorDataHash ∷ !(SafeHash c AnchorData)
- newtype AnchorData = AnchorData ByteString
- hashAnchorData ∷ ∀ c. Crypto c ⇒ AnchorData → SafeHash c AnchorData
- data Globals = Globals {}
- epochInfoPure ∷ Globals → EpochInfo Identity
- type ShelleyBase = ReaderT Globals Identity
- data Relation
- data Mismatch (r ∷ Relation) a = Mismatch {
- mismatchSupplied ∷ !a
- mismatchExpected ∷ !a
- swapMismatch ∷ Mismatch r a → (a, a)
- unswapMismatch ∷ (a, a) → Mismatch r a
- class Inject t s where
- inject ∷ t → s
Documentation
addEpochInterval ∷ EpochNo → EpochInterval → EpochNo Source #
Add a EpochInterval (a positive change) to an EpochNo to get a new EpochNo
binOpEpochNo ∷ (Word64 → Word64 → Word64) → EpochNo → EpochNo → EpochNo Source #
Convenience function for doing binary operations on two EpochNo
s
The 0-based index for the Ourboros time slot.
Instances
data WithOrigin t Source #
Instances
An epoch, i.e. the number of the epoch.
Instances
Instances
newtype EpochInterval Source #
Instances
The 0-based index of the block in the blockchain. BlockNo is <= SlotNo and is only equal at slot N if there is a block for every slot where N <= SlotNo.
Instances
Instances
FromJSON ProtVer Source # | |
ToJSON ProtVer Source # | |
Generic ProtVer Source # | |
Show ProtVer Source # | |
FromCBOR ProtVer Source # | |
ToCBOR ProtVer Source # | |
DecCBOR ProtVer Source # | |
EncCBOR ProtVer Source # | |
DecCBORGroup ProtVer Source # | |
Defined in Cardano.Ledger.BaseTypes | |
EncCBORGroup ProtVer Source # | |
ToPlutusData ProtVer Source # | |
Defined in Cardano.Ledger.Plutus.ToPlutusData | |
NFData ProtVer Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq ProtVer Source # | |
Ord ProtVer Source # | |
Defined in Cardano.Ledger.BaseTypes | |
NoThunks ProtVer Source # | |
type Rep ProtVer Source # | |
Defined in Cardano.Ledger.BaseTypes type Rep ProtVer = D1 ('MetaData "ProtVer" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.16.0.0-inplace" 'False) (C1 ('MetaCons "ProtVer" 'PrefixI 'True) (S1 ('MetaSel ('Just "pvMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Just "pvMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural))) |
type FixedPoint = Digits34 Source #
Instances
FromJSON Network Source # | |
ToJSON Network Source # | |
Bounded Network Source # | |
Enum Network Source # | |
Defined in Cardano.Ledger.BaseTypes succ ∷ Network → Network Source # pred ∷ Network → Network Source # toEnum ∷ Int → Network Source # fromEnum ∷ Network → Int Source # enumFrom ∷ Network → [Network] Source # enumFromThen ∷ Network → Network → [Network] Source # enumFromTo ∷ Network → Network → [Network] Source # enumFromThenTo ∷ Network → Network → Network → [Network] Source # | |
Generic Network Source # | |
Show Network Source # | |
DecCBOR Network Source # | |
EncCBOR Network Source # | |
Default Network Source # | |
Defined in Cardano.Ledger.BaseTypes | |
NFData Network Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq Network Source # | |
Ord Network Source # | |
Defined in Cardano.Ledger.BaseTypes | |
NoThunks Network Source # | |
type Rep Network Source # | |
Evolving nonce type.
Nonce !(Hash Blake2b_256 Nonce) | |
NeutralNonce | Identity element |
Instances
FromJSON Nonce Source # | |
ToJSON Nonce Source # | |
Generic Nonce Source # | |
Show Nonce Source # | |
FromCBOR Nonce Source # | |
ToCBOR Nonce Source # | |
DecCBOR Nonce Source # | |
EncCBOR Nonce Source # | |
NFData Nonce Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq Nonce Source # | |
Ord Nonce Source # | |
NoThunks Nonce Source # | |
type Rep Nonce Source # | |
Defined in Cardano.Ledger.BaseTypes type Rep Nonce = D1 ('MetaData "Nonce" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.16.0.0-inplace" 'False) (C1 ('MetaCons "Nonce" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash Blake2b_256 Nonce))) :+: C1 ('MetaCons "NeutralNonce" 'PrefixI 'False) (U1 ∷ Type → Type)) |
Seed to the verifiable random function.
data UnitInterval Source #
Type to represent a value in the unit interval [0; 1]
Instances
data PositiveUnitInterval Source #
Type to represent a value in the unit interval (0; 1]
Instances
data PositiveInterval Source #
Type to represent a value in the interval (0; +∞)
Instances
data NonNegativeInterval Source #
Type to represent a value in the interval [0; +∞)
Instances
class Bounded r ⇒ BoundedRational r where Source #
Type clases that allows conversion between Rational
and some form of bounded
rational type. Bounds can be restricted by both the Bounded
type class and underlyng
representation.
maybe True (\br -> minBound <= br && br <= maxBound) . boundRational
Roundtrip properties must hold:
\r -> maybe True ((r ==) . unboundRational) (boundRational r) \br -> Just br == boundRational (unboundRational br)
boundRational ∷ Rational → Maybe r Source #
Returns Nothing
when supplied value is not within bounds or when precision is
too high to be represented by the underlying type
Example
>>>
:set -XTypeApplications
>>>
import Data.Ratio
>>>
boundRational @UnitInterval $ 2 % 3
Just (2 % 3)>>>
boundRational @UnitInterval (-0.5)
Nothing>>>
boundRational @UnitInterval (1.5)
Nothing>>>
boundRational @UnitInterval 0
Just (0 % 1)>>>
boundRational @PositiveUnitInterval 0
Nothing
unboundRational ∷ r → Rational Source #
Promote bounded rational type into the unbounded Rational
.
invalidKey ∷ MonadFail m ⇒ Word → m a Source #
Report an error when a numeric key of the type constructor doesn't match.
mkNonceFromOutputVRF ∷ OutputVRF v → Nonce Source #
Make a nonce from the VRF output bytes
mkNonceFromNumber ∷ Word64 → Nonce Source #
Make a nonce from a number.
Instances
textToUrl ∷ MonadFail m ⇒ Int → Text → m Url Source #
Turn a Text into a Url, fail if the Text has more than n
Bytes
Instances
FromJSON DnsName Source # | |
ToJSON DnsName Source # | |
Generic DnsName Source # | |
Show DnsName Source # | |
DecCBOR DnsName Source # | |
EncCBOR DnsName Source # | |
NFData DnsName Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq DnsName Source # | |
Ord DnsName Source # | |
Defined in Cardano.Ledger.BaseTypes | |
NoThunks DnsName Source # | |
type Rep DnsName Source # | |
Defined in Cardano.Ledger.BaseTypes |
textToDns ∷ MonadFail m ⇒ Int → Text → m DnsName Source #
Turn a Text into a DnsName, fail if the Text has more than n
Bytes
Instances
FromJSON Port Source # | |
ToJSON Port Source # | |
Generic Port Source # | |
Num Port Source # | |
Show Port Source # | |
DecCBOR Port Source # | |
EncCBOR Port Source # | |
NFData Port Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq Port Source # | |
Ord Port Source # | |
NoThunks Port Source # | |
type Rep Port Source # | |
Defined in Cardano.Ledger.BaseTypes |
data ActiveSlotCoeff Source #
Instances
module Data.Maybe.Strict
newtype BlocksMade c Source #
Number of blocks which have been created by stake pools in the current epoch.
BlocksMade | |
|
Instances
Indices
Transaction index.
Instances
ToJSON TxIx Source # | |
Bounded TxIx Source # | |
Enum TxIx Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Generic TxIx Source # | |
Show TxIx Source # | |
FromCBOR TxIx Source # | |
ToCBOR TxIx Source # | |
DecCBOR TxIx Source # | |
EncCBOR TxIx Source # | |
NFData TxIx Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq TxIx Source # | |
Ord TxIx Source # | |
NoThunks TxIx Source # | |
type Rep TxIx Source # | |
Defined in Cardano.Ledger.BaseTypes |
mkTxIxPartial ∷ HasCallStack ⇒ Integer → TxIx Source #
Certificate index. Use certIxFromIntegral
in order to construct this
index safely from anything other than Word16
. There is also
mkCertIxPartial
that can be used for testing.
Instances
ToJSON CertIx Source # | |
Bounded CertIx Source # | |
Enum CertIx Source # | |
Defined in Cardano.Ledger.BaseTypes succ ∷ CertIx → CertIx Source # pred ∷ CertIx → CertIx Source # toEnum ∷ Int → CertIx Source # fromEnum ∷ CertIx → Int Source # enumFrom ∷ CertIx → [CertIx] Source # enumFromThen ∷ CertIx → CertIx → [CertIx] Source # enumFromTo ∷ CertIx → CertIx → [CertIx] Source # enumFromThenTo ∷ CertIx → CertIx → CertIx → [CertIx] Source # | |
Show CertIx Source # | |
FromCBOR CertIx Source # | |
ToCBOR CertIx Source # | |
DecCBOR CertIx Source # | |
EncCBOR CertIx Source # | |
NFData CertIx Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq CertIx Source # | |
Ord CertIx Source # | |
Defined in Cardano.Ledger.BaseTypes | |
NoThunks CertIx Source # | |
certIxToInt ∷ CertIx → Int Source #
Anchor | |
|
Instances
Crypto c ⇒ FromJSON (Anchor c) Source # | |
Crypto c ⇒ ToJSON (Anchor c) Source # | |
Generic (Anchor c) Source # | |
Show (Anchor c) Source # | |
Crypto c ⇒ DecCBOR (Anchor c) Source # | |
Crypto c ⇒ EncCBOR (Anchor c) Source # | |
Crypto c ⇒ Default (Anchor c) Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Crypto c ⇒ NFData (Anchor c) Source # | |
Defined in Cardano.Ledger.BaseTypes | |
Eq (Anchor c) Source # | |
Ord (Anchor c) Source # | |
NoThunks (Anchor c) Source # | |
type Rep (Anchor c) Source # | |
Defined in Cardano.Ledger.BaseTypes type Rep (Anchor c) = D1 ('MetaData "Anchor" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.16.0.0-inplace" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "anchorUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "anchorDataHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SafeHash c AnchorData)))) |
newtype AnchorData Source #
Instances
SafeToHash AnchorData Source # | |
Defined in Cardano.Ledger.BaseTypes originalBytes ∷ AnchorData → ByteString Source # originalBytesSize ∷ AnchorData → Int Source # makeHashWithExplicitProxys ∷ HashAlgorithm (HASH c) ⇒ Proxy c → Proxy index → AnchorData → SafeHash c index Source # | |
Eq AnchorData Source # | |
Defined in Cardano.Ledger.BaseTypes (==) ∷ AnchorData → AnchorData → Bool Source # (/=) ∷ AnchorData → AnchorData → Bool Source # | |
HashWithCrypto AnchorData AnchorData Source # | |
Defined in Cardano.Ledger.BaseTypes hashWithCrypto ∷ HashAlgorithm (HASH c) ⇒ Proxy c → AnchorData → SafeHash c AnchorData Source # |
hashAnchorData ∷ ∀ c. Crypto c ⇒ AnchorData → SafeHash c AnchorData Source #
Hash AnchorData
STS Base
Globals | |
|
Instances
epochInfoPure ∷ Globals → EpochInfo Identity Source #
Pure epoch info via throw. Note that this should only be used when we can
guarantee the validity of the translation; in particular, the EpochInfo
used here should never be applied to user-supplied input.
Relationship descriptor for the expectation in the Mismatch
type.
RelEQ | Equal |
RelLT | Less then |
RelGT | Greater then |
RelLTEQ | Less then or equal |
RelGTEQ | Greater then or equal |
RelSubset | Is subset of |
Instances
data Mismatch (r ∷ Relation) a Source #
This is intended to help clarify supplied and expected values reported by predicate-failures in all eras.
Mismatch | |
|
Instances
swapMismatch ∷ Mismatch r a → (a, a) Source #
Convert a Mismatch
to a tuple that has "supplied" and "expected" swapped places
unswapMismatch ∷ (a, a) → Mismatch r a Source #
Convert a tuple that has "supplied" and "expected" swapped places to a Mismatch
type.