Copyright | (c) 2023 GYELD GMBH |
---|---|
License | Apache 2.0 |
Maintainer | [email protected] |
Stability | develop |
Safe Haskell | None |
Language | GHC2021 |
GeniusYield.Imports
Contents
Description
Synopsis
- module Data.Functor.Const
- module Data.Functor.Identity
- bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d
- first :: Bifunctor p => (a -> b) -> p a c -> p b c
- second :: Bifunctor p => (b -> c) -> p a b -> p a c
- void :: Functor f => f a -> f ()
- data Natural
- data Void
- join :: Monad m => m (m a) -> m a
- toList :: Foldable t => t a -> [a]
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- class Generic a
- class IsString a where
- fromString :: String -> a
- guard :: Alternative f => Bool -> f ()
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- absurd :: Void -> a
- when :: Applicative f => Bool -> f () -> f ()
- ap :: Monad m => m (a -> b) -> m a -> m b
- isJust :: Maybe a -> Bool
- fromMaybe :: a -> Maybe a -> a
- catMaybes :: Filterable f => f (Maybe a) -> f a
- mapMaybe :: Filterable f => (a -> Maybe b) -> f a -> f b
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- isAlphaNum :: Char -> Bool
- data Proxy (t :: k) = Proxy
- find :: Foldable t => (a -> Bool) -> t a -> Maybe a
- class (Typeable e, Show e) => Exception e
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- catch :: Exception e => IO a -> (e -> IO a) -> IO a
- throwIO :: (HasCallStack, Exception e) => e -> IO a
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- unless :: Applicative f => Bool -> f () -> f ()
- data Set a
- data Map k a
- (&) :: a -> (a -> b) -> b
- coerce :: Coercible a b => a -> b
- type Type = TYPE LiftedRep
- type Constraint = CONSTRAINT LiftedRep
- data Text
- data CallStack
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- class Contravariant (f :: Type -> Type) where
- class ToJSON a where
- toJSON :: a -> Value
- toEncoding :: a -> Encoding
- toJSONList :: [a] -> Value
- toEncodingList :: [a] -> Encoding
- omitField :: a -> Bool
- class FromJSON a where
- parseJSON :: Value -> Parser a
- parseJSONList :: Value -> Parser [a]
- omittedField :: Maybe a
- (>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c
- type HasCallStack = ?callStack :: CallStack
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- isHexDigit :: Char -> Bool
- fromRight :: b -> Either a b -> b
- data (a :: k) :~: (b :: k) where
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- class PrintfArg a where
- formatArg :: a -> FieldFormatter
- parseFormat :: a -> ModifierParser
- printf :: PrintfType r => String -> r
- wither :: (Witherable t, Applicative f) => (a -> f (Maybe b)) -> t a -> f (t b)
- data Some (tag :: k -> Type) where
- encodeUtf8 :: Text -> ByteString
- rightToMaybe :: Either a b -> Maybe b
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- withSome :: Some tag -> (forall (a :: k). tag a -> b) -> b
- iwither :: (WitherableWithIndex i t, Applicative f) => (i -> a -> f (Maybe b)) -> t a -> f (t b)
- pattern TODO :: () => HasCallStack => a
- findFirst :: Foldable f => (a -> Maybe b) -> f a -> Maybe b
- decodeUtf8Lenient :: ByteString -> Text
- lazyDecodeUtf8Lenient :: ByteString -> Text
- hush :: Either e a -> Maybe a
- hoistMaybe :: forall (m :: Type -> Type) b. Applicative m => Maybe b -> MaybeT m b
Documentation
module Data.Functor.Const
module Data.Functor.Identity
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing
>>>
void (Just 3)
Just ()
Replace the contents of an
with unit, resulting in an Either
Int
Int
:Either
Int
()
>>>
void (Left 8675309)
Left 8675309
>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]
>>>
void $ mapM print [1,2]
1 2
Natural number
Invariant: numbers <= 0xffffffffffffffff use the NS
constructor
Instances
Uninhabited data type
@since base-4.8.0.0
Instances
HasTrie Void | |||||
FromJSON Void | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
FromJSONKey Void | Since: aeson-2.1.2.0 | ||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON Void | |||||
ToJSONKey Void | Since: aeson-2.1.2.0 | ||||
Defined in Data.Aeson.Types.ToJSON | |||||
FromCBOR Void | |||||
ToCBOR Void | |||||
DecCBOR Void | |||||
EncCBOR Void | |||||
NFData Void | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Semigroup Void | @since base-4.9.0.0 | ||||
Exception Void | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Exception.Type Methods toException :: Void -> SomeException # fromException :: SomeException -> Maybe Void # displayException :: Void -> String # backtraceDesired :: Void -> Bool # | |||||
Generic Void | |||||
Read Void | Reading a @since base-4.8.0.0 | ||||
Show Void | @since base-4.8.0.0 | ||||
Eq Void | @since base-4.8.0.0 | ||||
Ord Void | @since base-4.8.0.0 | ||||
Hashable Void | |||||
Defined in Data.Hashable.Class | |||||
FromFormKey Void | |||||
Defined in Web.Internal.FormUrlEncoded | |||||
ToFormKey Void | |||||
Defined in Web.Internal.FormUrlEncoded | |||||
FromHttpApiData Void | Parsing a | ||||
Defined in Web.Internal.HttpApiData | |||||
ToHttpApiData Void | |||||
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Void -> Text # toEncodedUrlPiece :: Void -> Builder # toHeader :: Void -> ByteString # toQueryParam :: Void -> Text # toEncodedQueryParam :: Void -> Builder # | |||||
ShowErrorComponent Void | |||||
Defined in Text.Megaparsec.Error | |||||
MemPack Void | |||||
NoThunks Void | |||||
Condense Void | |||||
Defined in Ouroboros.Consensus.Util.Condense | |||||
HasBlueprintDefinition Void | |||||
Defined in PlutusTx.Blueprint.Definition.Unroll Associated Types
Methods | |||||
FromData Void | |||||
Defined in PlutusTx.IsData.Class Methods fromBuiltinData :: BuiltinData -> Maybe Void # | |||||
ToData Void | |||||
Defined in PlutusTx.IsData.Class Methods toBuiltinData :: Void -> BuiltinData # | |||||
UnsafeFromData Void | |||||
Defined in PlutusTx.IsData.Class Methods | |||||
Pretty Void | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.
| ||||
Defined in Prettyprinter.Internal | |||||
Serialise Void | Since: serialise-0.2.4.0 | ||||
DefaultPrettyBy config Void | |||||
Defined in Text.PrettyBy.Internal Methods defaultPrettyBy :: config -> Void -> Doc ann # defaultPrettyListBy :: config -> [Void] -> Doc ann # | |||||
PrettyDefaultBy config Void => PrettyBy config Void |
| ||||
Defined in Text.PrettyBy.Internal | |||||
Lift Void | Since: template-haskell-2.15.0.0 | ||||
FoldableWithIndex Void (Proxy :: Type -> Type) | |||||
Defined in WithIndex | |||||
FoldableWithIndex Void (U1 :: Type -> Type) | |||||
FoldableWithIndex Void (V1 :: Type -> Type) | |||||
FunctorWithIndex Void (Proxy :: Type -> Type) | |||||
FunctorWithIndex Void (U1 :: Type -> Type) | |||||
FunctorWithIndex Void (V1 :: Type -> Type) | |||||
TraversableWithIndex Void (Proxy :: Type -> Type) | |||||
TraversableWithIndex Void (U1 :: Type -> Type) | |||||
TraversableWithIndex Void (V1 :: Type -> Type) | |||||
FilterableWithIndex Void (Proxy :: Type -> Type) | |||||
WitherableWithIndex Void (Proxy :: Type -> Type) | |||||
FoldableWithIndex Void (Const e :: Type -> Type) | |||||
Defined in WithIndex | |||||
FoldableWithIndex Void (Constant e :: Type -> Type) | |||||
Defined in WithIndex Methods ifoldMap :: Monoid m => (Void -> a -> m) -> Constant e a -> m # ifoldMap' :: Monoid m => (Void -> a -> m) -> Constant e a -> m # ifoldr :: (Void -> a -> b -> b) -> b -> Constant e a -> b # ifoldl :: (Void -> b -> a -> b) -> b -> Constant e a -> b # ifoldr' :: (Void -> a -> b -> b) -> b -> Constant e a -> b # ifoldl' :: (Void -> b -> a -> b) -> b -> Constant e a -> b # | |||||
FunctorWithIndex Void (Const e :: Type -> Type) | |||||
FunctorWithIndex Void (Constant e :: Type -> Type) | |||||
TraversableWithIndex Void (Const e :: Type -> Type) | |||||
TraversableWithIndex Void (Constant e :: Type -> Type) | |||||
FoldableWithIndex Void (K1 i c :: Type -> Type) | |||||
Defined in WithIndex | |||||
FunctorWithIndex Void (K1 i c :: Type -> Type) | |||||
TraversableWithIndex Void (K1 i c :: Type -> Type) | |||||
Newtype (Void :->: a) | |||||
data Void :->: a | |||||
Defined in Data.MemoTrie | |||||
type Code Void | |||||
Defined in Generics.SOP.Instances | |||||
type DatatypeInfoOf Void | |||||
Defined in Generics.SOP.Instances type DatatypeInfoOf Void = 'ADT "GHC.Internal.Base" "Void" ('[] :: [ConstructorInfo]) ('[] :: [[StrictnessInfo]]) | |||||
type Rep Void | @since base-4.8.0.0 | ||||
type Unroll Void | |||||
Defined in PlutusTx.Blueprint.Definition.Unroll | |||||
type IsBuiltin DefaultUni Void | |||||
Defined in PlutusCore.Examples.Builtins | |||||
type ToBinds DefaultUni acc Void | |||||
Defined in PlutusCore.Examples.Builtins | |||||
type ToHoles DefaultUni _1 Void | |||||
Defined in PlutusCore.Examples.Builtins | |||||
type O (Void :->: a) | |||||
Defined in Data.MemoTrie |
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the join
bssdo
expression
do bs <- bss bs
Examples
>>>
join [[1, 2, 3], [4, 5, 6], [7, 8, 9]]
[1,2,3,4,5,6,7,8,9]
>>>
join (Just (Just 3))
Just 3
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
toList :: Foldable t => t a -> [a] #
List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.
Examples
Basic usage:
>>>
toList Nothing
[]
>>>
toList (Just 42)
[42]
>>>
toList (Left "foo")
[]
>>>
toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
[5,17,12,8]
For lists, toList
is the identity:
>>>
toList [1, 2, 3]
[1,2,3]
@since base-4.8.0.0
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to Weak Head Normal
Form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a
finite structure to a single strict result (e.g. sum
).
For a general Foldable
structure this should be semantically identical
to,
foldl' f z =foldl'
f z .toList
@since base-4.6.0.0
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
Generic CabalSpecVersion | |||||
Defined in Distribution.CabalSpecVersion Associated Types
Methods from :: CabalSpecVersion -> Rep CabalSpecVersion x # to :: Rep CabalSpecVersion x -> CabalSpecVersion # | |||||
Generic PError | |||||
Defined in Distribution.Parsec.Error Associated Types
| |||||
Generic Position | |||||
Defined in Distribution.Parsec.Position Associated Types
| |||||
Generic PWarnType | |||||
Defined in Distribution.Parsec.Warning Associated Types
| |||||
Generic PWarning | |||||
Defined in Distribution.Parsec.Warning Associated Types
| |||||
Generic Arch | |||||
Defined in Distribution.System Associated Types
| |||||
Generic OS | |||||
Defined in Distribution.System Associated Types
| |||||
Generic Platform | |||||
Defined in Distribution.System Associated Types
| |||||
Generic Structure | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic Value | |||||
Defined in Data.Aeson.Types.Internal Associated Types
| |||||
Generic AdjacencyIntMap | |||||
Defined in Algebra.Graph.AdjacencyIntMap Associated Types
Methods from :: AdjacencyIntMap -> Rep AdjacencyIntMap x # to :: Rep AdjacencyIntMap x -> AdjacencyIntMap # | |||||
Generic BalanceInsufficientError # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: BalanceInsufficientError -> Rep BalanceInsufficientError x # to :: Rep BalanceInsufficientError x -> BalanceInsufficientError # | |||||
Generic SelectionBalanceError # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: SelectionBalanceError -> Rep SelectionBalanceError x # to :: Rep SelectionBalanceError x -> SelectionBalanceError # | |||||
Generic SelectionConstraints # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: SelectionConstraints -> Rep SelectionConstraints x # to :: Rep SelectionConstraints x -> SelectionConstraints # | |||||
Generic UnableToConstructChangeError # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
| |||||
Generic ValueSizeAssessment # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: ValueSizeAssessment -> Rep ValueSizeAssessment x # to :: Rep ValueSizeAssessment x -> ValueSizeAssessment # | |||||
Generic GYAddress # | |||||
Defined in GeniusYield.Types.Address Associated Types
| |||||
Generic GYStakeAddress # | |||||
Defined in GeniusYield.Types.Address Associated Types
Methods from :: GYStakeAddress -> Rep GYStakeAddress x # to :: Rep GYStakeAddress x -> GYStakeAddress # | |||||
Generic ContractBlueprint # | |||||
Defined in GeniusYield.Types.Blueprint.Contract Associated Types
Methods from :: ContractBlueprint -> Rep ContractBlueprint x # to :: Rep ContractBlueprint x -> ContractBlueprint # | |||||
Generic ParameterBlueprint # | |||||
Defined in GeniusYield.Types.Blueprint.Parameter Associated Types
Methods from :: ParameterBlueprint -> Rep ParameterBlueprint x # to :: Rep ParameterBlueprint x -> ParameterBlueprint # | |||||
Generic Purpose # | |||||
Defined in GeniusYield.Types.Blueprint.Purpose Associated Types
| |||||
Generic ConstructorSchema # | |||||
Defined in GeniusYield.Types.Blueprint.Schema Associated Types
Methods from :: ConstructorSchema -> Rep ConstructorSchema x # to :: Rep ConstructorSchema x -> ConstructorSchema # | |||||
Generic IntegerSchema # | |||||
Defined in GeniusYield.Types.Blueprint.Schema Associated Types
| |||||
Generic MapSchema # | |||||
Defined in GeniusYield.Types.Blueprint.Schema Associated Types
| |||||
Generic PairSchema # | |||||
Defined in GeniusYield.Types.Blueprint.Schema Associated Types
| |||||
Generic GYNatural # | |||||
Defined in GeniusYield.Types.Natural Associated Types
| |||||
Generic GYNetworkInfo # | |||||
Defined in GeniusYield.Types.NetworkId Associated Types
| |||||
Generic GYStakePoolRelay # | |||||
Defined in GeniusYield.Types.Pool Associated Types
Methods from :: GYStakePoolRelay -> Rep GYStakePoolRelay x # to :: Rep GYStakePoolRelay x -> GYStakePoolRelay # | |||||
Generic GYRational # | |||||
Defined in GeniusYield.Types.Rational Associated Types
| |||||
Generic GYAssetClass # | |||||
Defined in GeniusYield.Types.Value Associated Types
| |||||
Generic GYNonAdaToken # | |||||
Defined in GeniusYield.Types.Value Associated Types
| |||||
Generic Alphabet | |||||
Defined in Data.ByteString.Base58.Internal Associated Types
| |||||
Generic ByteString64 | |||||
Defined in Data.ByteString.Base64.Type Associated Types
| |||||
Generic Project | |||||
Defined in Blockfrost.Auth Associated Types
| |||||
Generic Env | |||||
Defined in Blockfrost.Env Associated Types
| |||||
Generic ApiError | |||||
Defined in Blockfrost.Types.ApiError Associated Types
| |||||
Generic AccountDelegation | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AccountDelegation -> Rep AccountDelegation x # to :: Rep AccountDelegation x -> AccountDelegation # | |||||
Generic AccountHistory | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AccountHistory -> Rep AccountHistory x # to :: Rep AccountHistory x -> AccountHistory # | |||||
Generic AccountInfo | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
| |||||
Generic AccountMir | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
| |||||
Generic AccountRegistration | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AccountRegistration -> Rep AccountRegistration x # to :: Rep AccountRegistration x -> AccountRegistration # | |||||
Generic AccountRegistrationAction | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AccountRegistrationAction -> Rep AccountRegistrationAction x # to :: Rep AccountRegistrationAction x -> AccountRegistrationAction # | |||||
Generic AccountReward | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
| |||||
Generic AccountWithdrawal | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AccountWithdrawal -> Rep AccountWithdrawal x # to :: Rep AccountWithdrawal x -> AccountWithdrawal # | |||||
Generic AddressAssociated | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AddressAssociated -> Rep AddressAssociated x # to :: Rep AddressAssociated x -> AddressAssociated # | |||||
Generic AddressAssociatedTotal | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
Methods from :: AddressAssociatedTotal -> Rep AddressAssociatedTotal x # to :: Rep AddressAssociatedTotal x -> AddressAssociatedTotal # | |||||
Generic RewardType | |||||
Defined in Blockfrost.Types.Cardano.Accounts Associated Types
| |||||
Generic AddressDetails | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
Methods from :: AddressDetails -> Rep AddressDetails x # to :: Rep AddressDetails x -> AddressDetails # | |||||
Generic AddressInfo | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
| |||||
Generic AddressInfoExtended | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
Methods from :: AddressInfoExtended -> Rep AddressInfoExtended x # to :: Rep AddressInfoExtended x -> AddressInfoExtended # | |||||
Generic AddressTransaction | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
Methods from :: AddressTransaction -> Rep AddressTransaction x # to :: Rep AddressTransaction x -> AddressTransaction # | |||||
Generic AddressType | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
| |||||
Generic AddressUtxo | |||||
Defined in Blockfrost.Types.Cardano.Addresses Associated Types
| |||||
Generic AssetAction | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetAddress | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetDetails | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetHistory | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetInfo | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetMetadata | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
| |||||
Generic AssetOnChainMetadata | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
Methods from :: AssetOnChainMetadata -> Rep AssetOnChainMetadata x # to :: Rep AssetOnChainMetadata x -> AssetOnChainMetadata # | |||||
Generic AssetTransaction | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
Methods from :: AssetTransaction -> Rep AssetTransaction x # to :: Rep AssetTransaction x -> AssetTransaction # | |||||
Generic MetadataMediaFile | |||||
Defined in Blockfrost.Types.Cardano.Assets Associated Types
Methods from :: MetadataMediaFile -> Rep MetadataMediaFile x # to :: Rep MetadataMediaFile x -> MetadataMediaFile # | |||||
Generic Block | |||||
Defined in Blockfrost.Types.Cardano.Blocks Associated Types
| |||||
Generic TxHashCBOR | |||||
Defined in Blockfrost.Types.Cardano.Blocks Associated Types
| |||||
Generic CostModels | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
| |||||
Generic CostModelsRaw | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
| |||||
Generic EpochInfo | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
| |||||
Generic PoolStakeDistribution | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
Methods from :: PoolStakeDistribution -> Rep PoolStakeDistribution x # to :: Rep PoolStakeDistribution x -> PoolStakeDistribution # | |||||
Generic ProtocolParams | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
Methods from :: ProtocolParams -> Rep ProtocolParams x # to :: Rep ProtocolParams x -> ProtocolParams # | |||||
Generic StakeDistribution | |||||
Defined in Blockfrost.Types.Cardano.Epochs Associated Types
Methods from :: StakeDistribution -> Rep StakeDistribution x # to :: Rep StakeDistribution x -> StakeDistribution # | |||||
Generic Genesis | |||||
Defined in Blockfrost.Types.Cardano.Genesis Associated Types
| |||||
Generic MempoolRedeemer | |||||
Defined in Blockfrost.Types.Cardano.Mempool Associated Types
Methods from :: MempoolRedeemer -> Rep MempoolRedeemer x # to :: Rep MempoolRedeemer x -> MempoolRedeemer # | |||||
Generic MempoolTransaction | |||||
Defined in Blockfrost.Types.Cardano.Mempool Associated Types
Methods from :: MempoolTransaction -> Rep MempoolTransaction x # to :: Rep MempoolTransaction x -> MempoolTransaction # | |||||
Generic MempoolUTxOInput | |||||
Defined in Blockfrost.Types.Cardano.Mempool Associated Types
Methods from :: MempoolUTxOInput -> Rep MempoolUTxOInput x # to :: Rep MempoolUTxOInput x -> MempoolUTxOInput # | |||||
Generic TransactionInMempool | |||||
Defined in Blockfrost.Types.Cardano.Mempool Associated Types
Methods from :: TransactionInMempool -> Rep TransactionInMempool x # to :: Rep TransactionInMempool x -> TransactionInMempool # | |||||
Generic TxMeta | |||||
Defined in Blockfrost.Types.Cardano.Metadata Associated Types
| |||||
Generic TxMetaCBOR | |||||
Defined in Blockfrost.Types.Cardano.Metadata Associated Types
| |||||
Generic TxMetaJSON | |||||
Defined in Blockfrost.Types.Cardano.Metadata Associated Types
| |||||
Generic Network | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
| |||||
Generic NetworkEraBound | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
Methods from :: NetworkEraBound -> Rep NetworkEraBound x # to :: Rep NetworkEraBound x -> NetworkEraBound # | |||||
Generic NetworkEraParameters | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
Methods from :: NetworkEraParameters -> Rep NetworkEraParameters x # to :: Rep NetworkEraParameters x -> NetworkEraParameters # | |||||
Generic NetworkEraSummary | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
Methods from :: NetworkEraSummary -> Rep NetworkEraSummary x # to :: Rep NetworkEraSummary x -> NetworkEraSummary # | |||||
Generic NetworkStake | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
| |||||
Generic NetworkSupply | |||||
Defined in Blockfrost.Types.Cardano.Network Associated Types
| |||||
Generic Pool | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolDelegator | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolEpoch | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolHistory | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolInfo | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolMetadata | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolMetadataResponse | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
Methods from :: PoolMetadataResponse -> Rep PoolMetadataResponse x # to :: Rep PoolMetadataResponse x -> PoolMetadataResponse # | |||||
Generic PoolRegistrationAction | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
Methods from :: PoolRegistrationAction -> Rep PoolRegistrationAction x # to :: Rep PoolRegistrationAction x -> PoolRegistrationAction # | |||||
Generic PoolRelay | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic PoolUpdate | |||||
Defined in Blockfrost.Types.Cardano.Pools Associated Types
| |||||
Generic InlineDatum | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic Script | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic ScriptCBOR | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic ScriptDatum | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic ScriptDatumCBOR | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
Methods from :: ScriptDatumCBOR -> Rep ScriptDatumCBOR x # to :: Rep ScriptDatumCBOR x -> ScriptDatumCBOR # | |||||
Generic ScriptJSON | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic ScriptRedeemer | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
Methods from :: ScriptRedeemer -> Rep ScriptRedeemer x # to :: Rep ScriptRedeemer x -> ScriptRedeemer # | |||||
Generic ScriptType | |||||
Defined in Blockfrost.Types.Cardano.Scripts Associated Types
| |||||
Generic PoolUpdateMetadata | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: PoolUpdateMetadata -> Rep PoolUpdateMetadata x # to :: Rep PoolUpdateMetadata x -> PoolUpdateMetadata # | |||||
Generic Pot | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
| |||||
Generic Transaction | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
| |||||
Generic TransactionCBOR | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionCBOR -> Rep TransactionCBOR x # to :: Rep TransactionCBOR x -> TransactionCBOR # | |||||
Generic TransactionDelegation | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionDelegation -> Rep TransactionDelegation x # to :: Rep TransactionDelegation x -> TransactionDelegation # | |||||
Generic TransactionMetaCBOR | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionMetaCBOR -> Rep TransactionMetaCBOR x # to :: Rep TransactionMetaCBOR x -> TransactionMetaCBOR # | |||||
Generic TransactionMetaJSON | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionMetaJSON -> Rep TransactionMetaJSON x # to :: Rep TransactionMetaJSON x -> TransactionMetaJSON # | |||||
Generic TransactionMir | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionMir -> Rep TransactionMir x # to :: Rep TransactionMir x -> TransactionMir # | |||||
Generic TransactionPoolRetiring | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionPoolRetiring -> Rep TransactionPoolRetiring x # to :: Rep TransactionPoolRetiring x -> TransactionPoolRetiring # | |||||
Generic TransactionPoolUpdate | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionPoolUpdate -> Rep TransactionPoolUpdate x # to :: Rep TransactionPoolUpdate x -> TransactionPoolUpdate # | |||||
Generic TransactionRedeemer | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionRedeemer -> Rep TransactionRedeemer x # to :: Rep TransactionRedeemer x -> TransactionRedeemer # | |||||
Generic TransactionStake | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionStake -> Rep TransactionStake x # to :: Rep TransactionStake x -> TransactionStake # | |||||
Generic TransactionUtxos | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionUtxos -> Rep TransactionUtxos x # to :: Rep TransactionUtxos x -> TransactionUtxos # | |||||
Generic TransactionWithdrawal | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
Methods from :: TransactionWithdrawal -> Rep TransactionWithdrawal x # to :: Rep TransactionWithdrawal x -> TransactionWithdrawal # | |||||
Generic UtxoInput | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
| |||||
Generic UtxoOutput | |||||
Defined in Blockfrost.Types.Cardano.Transactions Associated Types
| |||||
Generic DerivedAddress | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
Methods from :: DerivedAddress -> Rep DerivedAddress x # to :: Rep DerivedAddress x -> DerivedAddress # | |||||
Generic TxEval | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
| |||||
Generic TxEvalBudget | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
| |||||
Generic TxEvalFailure | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
| |||||
Generic TxEvalInput | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
| |||||
Generic TxEvalValidator | |||||
Defined in Blockfrost.Types.Cardano.Utils Associated Types
Methods from :: TxEvalValidator -> Rep TxEvalValidator x # to :: Rep TxEvalValidator x -> TxEvalValidator # | |||||
Generic Healthy | |||||
Defined in Blockfrost.Types.Common Associated Types
| |||||
Generic Metric | |||||
Defined in Blockfrost.Types.Common Associated Types
| |||||
Generic ServerTime | |||||
Defined in Blockfrost.Types.Common Associated Types
| |||||
Generic URLVersion | |||||
Defined in Blockfrost.Types.Common Associated Types
| |||||
Generic IPFSAdd | |||||
Defined in Blockfrost.Types.IPFS Associated Types
| |||||
Generic IPFSData | |||||
Defined in Blockfrost.Types.IPFS Associated Types
| |||||
Generic IPFSPin | |||||
Defined in Blockfrost.Types.IPFS Associated Types
| |||||
Generic IPFSPinChange | |||||
Defined in Blockfrost.Types.IPFS Associated Types
| |||||
Generic PinState | |||||
Defined in Blockfrost.Types.IPFS Associated Types
| |||||
Generic NutlinkAddress | |||||
Defined in Blockfrost.Types.NutLink Associated Types
Methods from :: NutlinkAddress -> Rep NutlinkAddress x # to :: Rep NutlinkAddress x -> NutlinkAddress # | |||||
Generic NutlinkAddressTicker | |||||
Defined in Blockfrost.Types.NutLink Associated Types
Methods from :: NutlinkAddressTicker -> Rep NutlinkAddressTicker x # to :: Rep NutlinkAddressTicker x -> NutlinkAddressTicker # | |||||
Generic NutlinkTicker | |||||
Defined in Blockfrost.Types.NutLink Associated Types
| |||||
Generic Address | |||||
Defined in Blockfrost.Types.Shared.Address Associated Types
| |||||
Generic Amount | |||||
Defined in Blockfrost.Types.Shared.Amount Associated Types
| |||||
Generic AmountExtended | |||||
Defined in Blockfrost.Types.Shared.Amount Associated Types
Methods from :: AmountExtended -> Rep AmountExtended x # to :: Rep AmountExtended x -> AmountExtended # | |||||
Generic AssetId | |||||
Defined in Blockfrost.Types.Shared.AssetId Associated Types
| |||||
Generic BlockHash | |||||
Defined in Blockfrost.Types.Shared.BlockHash Associated Types
| |||||
Generic BlockIndex | |||||
Defined in Blockfrost.Types.Shared.BlockIndex Associated Types
| |||||
Generic DatumHash | |||||
Defined in Blockfrost.Types.Shared.DatumHash Associated Types
| |||||
Generic Epoch | |||||
Defined in Blockfrost.Types.Shared.Epoch Associated Types
| |||||
Generic EpochLength | |||||
Defined in Blockfrost.Types.Shared.Epoch Associated Types
| |||||
Generic POSIXMillis | |||||
Defined in Blockfrost.Types.Shared.POSIXMillis Associated Types
| |||||
Generic PolicyId | |||||
Defined in Blockfrost.Types.Shared.PolicyId Associated Types
| |||||
Generic PoolId | |||||
Defined in Blockfrost.Types.Shared.PoolId Associated Types
| |||||
Generic Quantity | |||||
Defined in Blockfrost.Types.Shared.Quantity Associated Types
| |||||
Generic ScriptHash | |||||
Defined in Blockfrost.Types.Shared.ScriptHash Associated Types
| |||||
Generic ScriptHashList | |||||
Defined in Blockfrost.Types.Shared.ScriptHash Associated Types
Methods from :: ScriptHashList -> Rep ScriptHashList x # to :: Rep ScriptHashList x -> ScriptHashList # | |||||
Generic Slot | |||||
Defined in Blockfrost.Types.Shared.Slot Associated Types
| |||||
Generic TxHash | |||||
Defined in Blockfrost.Types.Shared.TxHash Associated Types
| |||||
Generic TxHashObject | |||||
Defined in Blockfrost.Types.Shared.TxHash Associated Types
| |||||
Generic ValidationPurpose | |||||
Defined in Blockfrost.Types.Shared.ValidationPurpose Associated Types
Methods from :: ValidationPurpose -> Rep ValidationPurpose x # to :: Rep ValidationPurpose x -> ValidationPurpose # | |||||
Generic ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods from :: ShortByteString -> Rep ShortByteString x # to :: Rep ShortByteString x -> ShortByteString # | |||||
Generic Address | |||||
Defined in Cardano.Address Associated Types
| |||||
Generic AddressDiscrimination | |||||
Defined in Cardano.Address Associated Types
Methods from :: AddressDiscrimination -> Rep AddressDiscrimination x # to :: Rep AddressDiscrimination x -> AddressDiscrimination # | |||||
Generic ChainPointer | |||||
Defined in Cardano.Address Associated Types
| |||||
Generic NetworkTag | |||||
Defined in Cardano.Address Associated Types
| |||||
Generic KeyHash | |||||
Defined in Cardano.Address.KeyHash Associated Types
| |||||
Generic KeyRole | |||||
Defined in Cardano.Address.KeyHash Associated Types
| |||||
Generic Cosigner | |||||
Defined in Cardano.Address.Script Associated Types
| |||||
Generic ScriptHash | |||||
Defined in Cardano.Address.Script Associated Types
| |||||
Generic ScriptTemplate | |||||
Defined in Cardano.Address.Script Associated Types
Methods from :: ScriptTemplate -> Rep ScriptTemplate x # to :: Rep ScriptTemplate x -> ScriptTemplate # | |||||
Generic ValidationLevel | |||||
Defined in Cardano.Address.Script Associated Types
Methods from :: ValidationLevel -> Rep ValidationLevel x # to :: Rep ValidationLevel x -> ValidationLevel # | |||||
Generic AddressInfo | |||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||
Generic ErrInspectAddress | |||||
Defined in Cardano.Address.Style.Byron Associated Types
Methods from :: ErrInspectAddress -> Rep ErrInspectAddress x # to :: Rep ErrInspectAddress x -> ErrInspectAddress # | |||||
Generic PayloadInfo | |||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||
Generic AddressInfo | |||||
Defined in Cardano.Address.Style.Icarus Associated Types
| |||||
Generic ErrInspectAddress | |||||
Defined in Cardano.Address.Style.Icarus Associated Types
Methods from :: ErrInspectAddress -> Rep ErrInspectAddress x # to :: Rep ErrInspectAddress x -> ErrInspectAddress # | |||||
Generic Role | |||||
Defined in Cardano.Address.Style.Icarus Associated Types
| |||||
Generic AddressInfo | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic ErrInspectAddress | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
Methods from :: ErrInspectAddress -> Rep ErrInspectAddress x # to :: Rep ErrInspectAddress x -> ErrInspectAddress # | |||||
Generic ErrInspectAddressOnlyShelley | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic ErrInvalidStakeAddress | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic InspectAddress | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
Methods from :: InspectAddress -> Rep InspectAddress x # to :: Rep InspectAddress x -> InspectAddress # | |||||
Generic ReferenceInfo | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic Role | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic MnemonicSize | |||||
Defined in Options.Applicative.MnemonicSize Associated Types
| |||||
Generic DoNotList | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic ImageObject | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic Reference | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic ReferenceType | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic Author | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic Reference | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic ReferenceHash | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic ReferenceType | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic Witness | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic WitnessAlgorithm | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic PraosNonce | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Associated Types
| |||||
Generic ProtocolParameters | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Associated Types
| |||||
Generic XPub | |||||
Defined in Cardano.Crypto.Wallet Associated Types
| |||||
Generic XPub | |||||
Defined in Cardano.Crypto.Wallet.Pure Associated Types
| |||||
Generic Point | |||||
Defined in Cardano.Crypto.VRF.Simple Associated Types
| |||||
Generic Output | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic Proof | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic SignKey | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic VerKey | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic Output | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
| |||||
Generic Proof | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
| |||||
Generic SignKey | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
| |||||
Generic VerKey | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
| |||||
Generic ProtocolMagicId | |||||
Defined in Cardano.Crypto.ProtocolMagic Associated Types
Methods from :: ProtocolMagicId -> Rep ProtocolMagicId x # to :: Rep ProtocolMagicId x -> ProtocolMagicId # | |||||
Generic RequiresNetworkMagic | |||||
Defined in Cardano.Crypto.ProtocolMagic Associated Types
Methods from :: RequiresNetworkMagic -> Rep RequiresNetworkMagic x # to :: Rep RequiresNetworkMagic x -> RequiresNetworkMagic # | |||||
Generic CompactRedeemVerificationKey | |||||
Defined in Cardano.Crypto.Signing.Redeem.Compact Associated Types
| |||||
Generic RedeemSigningKey | |||||
Defined in Cardano.Crypto.Signing.Redeem.SigningKey Associated Types
Methods from :: RedeemSigningKey -> Rep RedeemSigningKey x # to :: Rep RedeemSigningKey x -> RedeemSigningKey # | |||||
Generic RedeemVerificationKey | |||||
Defined in Cardano.Crypto.Signing.Redeem.VerificationKey Associated Types
Methods from :: RedeemVerificationKey -> Rep RedeemVerificationKey x # to :: Rep RedeemVerificationKey x -> RedeemVerificationKey # | |||||
Generic SignTag | |||||
Defined in Cardano.Crypto.Signing.Tag Associated Types
| |||||
Generic VerificationKey | |||||
Defined in Cardano.Crypto.Signing.VerificationKey Associated Types
Methods from :: VerificationKey -> Rep VerificationKey x # to :: Rep VerificationKey x -> VerificationKey # | |||||
Generic ValidityInterval | |||||
Defined in Cardano.Ledger.Allegra.Scripts Associated Types
Methods from :: ValidityInterval -> Rep ValidityInterval x # to :: Rep ValidityInterval x -> ValidityInterval # | |||||
Generic AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Associated Types
| |||||
Generic LangDepView | |||||
Defined in Cardano.Ledger.Alonzo.PParams Associated Types
| |||||
Generic FailureDescription | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Associated Types
Methods from :: FailureDescription -> Rep FailureDescription x # to :: Rep FailureDescription x -> FailureDescription # | |||||
Generic TagMismatchDescription | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Associated Types
Methods from :: TagMismatchDescription -> Rep TagMismatchDescription x # to :: Rep TagMismatchDescription x -> TagMismatchDescription # | |||||
Generic IsValid | |||||
Defined in Cardano.Ledger.Alonzo.Tx Associated Types
| |||||
Generic Addr28Extra | |||||
Defined in Cardano.Ledger.Alonzo.TxOut Associated Types
| |||||
Generic DataHash32 | |||||
Defined in Cardano.Ledger.Alonzo.TxOut Associated Types
| |||||
Generic CommitteeMemberState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: CommitteeMemberState -> Rep CommitteeMemberState x # to :: Rep CommitteeMemberState x -> CommitteeMemberState # | |||||
Generic CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: CommitteeMembersState -> Rep CommitteeMembersState x # to :: Rep CommitteeMembersState x -> CommitteeMembersState # | |||||
Generic HotCredAuthStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: HotCredAuthStatus -> Rep HotCredAuthStatus x # to :: Rep HotCredAuthStatus x -> HotCredAuthStatus # | |||||
Generic MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
| |||||
Generic NextEpochChange | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: NextEpochChange -> Rep NextEpochChange x # to :: Rep NextEpochChange x -> NextEpochChange # | |||||
Generic ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Associated Types
| |||||
Generic ToSign | |||||
Defined in Cardano.Chain.Block.Header Associated Types
| |||||
Generic Proof | |||||
Defined in Cardano.Chain.Block.Proof Associated Types
| |||||
Generic ChainValidationState | |||||
Defined in Cardano.Chain.Block.Validation Associated Types
Methods from :: ChainValidationState -> Rep ChainValidationState x # to :: Rep ChainValidationState x -> ChainValidationState # | |||||
Generic AddrAttributes | |||||
Defined in Cardano.Chain.Common.AddrAttributes Associated Types
Methods from :: AddrAttributes -> Rep AddrAttributes x # to :: Rep AddrAttributes x -> AddrAttributes # | |||||
Generic HDAddressPayload | |||||
Defined in Cardano.Chain.Common.AddrAttributes Associated Types
Methods from :: HDAddressPayload -> Rep HDAddressPayload x # to :: Rep HDAddressPayload x -> HDAddressPayload # | |||||
Generic AddrSpendingData | |||||
Defined in Cardano.Chain.Common.AddrSpendingData Associated Types
Methods from :: AddrSpendingData -> Rep AddrSpendingData x # to :: Rep AddrSpendingData x -> AddrSpendingData # | |||||
Generic AddrType | |||||
Defined in Cardano.Chain.Common.AddrSpendingData Associated Types
| |||||
Generic Address | |||||
Defined in Cardano.Chain.Common.Address Associated Types
| |||||
Generic Address' | |||||
Defined in Cardano.Chain.Common.Address Associated Types
| |||||
Generic UnparsedFields | |||||
Defined in Cardano.Chain.Common.Attributes Associated Types
Methods from :: UnparsedFields -> Rep UnparsedFields x # to :: Rep UnparsedFields x -> UnparsedFields # | |||||
Generic BlockCount | |||||
Defined in Cardano.Chain.Common.BlockCount Associated Types
| |||||
Generic ChainDifficulty | |||||
Defined in Cardano.Chain.Common.ChainDifficulty Associated Types
Methods from :: ChainDifficulty -> Rep ChainDifficulty x # to :: Rep ChainDifficulty x -> ChainDifficulty # | |||||
Generic CompactAddress | |||||
Defined in Cardano.Chain.Common.Compact Associated Types
Methods from :: CompactAddress -> Rep CompactAddress x # to :: Rep CompactAddress x -> CompactAddress # | |||||
Generic Lovelace | |||||
Defined in Cardano.Chain.Common.Lovelace Associated Types
| |||||
Generic LovelacePortion | |||||
Defined in Cardano.Chain.Common.LovelacePortion Associated Types
Methods from :: LovelacePortion -> Rep LovelacePortion x # to :: Rep LovelacePortion x -> LovelacePortion # | |||||
Generic NetworkMagic | |||||
Defined in Cardano.Chain.Common.NetworkMagic Associated Types
| |||||
Generic TxFeePolicy | |||||
Defined in Cardano.Chain.Common.TxFeePolicy Associated Types
| |||||
Generic TxSizeLinear | |||||
Defined in Cardano.Chain.Common.TxSizeLinear Associated Types
| |||||
Generic Map | |||||
Defined in Cardano.Chain.Delegation.Map Associated Types
| |||||
Generic State | |||||
Defined in Cardano.Chain.Delegation.Validation.Activation Associated Types
| |||||
Generic Environment | |||||
Defined in Cardano.Chain.Delegation.Validation.Interface Associated Types
| |||||
Generic State | |||||
Defined in Cardano.Chain.Delegation.Validation.Interface Associated Types
| |||||
Generic Environment | |||||
Defined in Cardano.Chain.Delegation.Validation.Scheduling Associated Types
| |||||
Generic ScheduledDelegation | |||||
Defined in Cardano.Chain.Delegation.Validation.Scheduling Associated Types
Methods from :: ScheduledDelegation -> Rep ScheduledDelegation x # to :: Rep ScheduledDelegation x -> ScheduledDelegation # | |||||
Generic State | |||||
Defined in Cardano.Chain.Delegation.Validation.Scheduling Associated Types
| |||||
Generic Config | |||||
Defined in Cardano.Chain.Genesis.Config Associated Types
| |||||
Generic GenesisData | |||||
Defined in Cardano.Chain.Genesis.Data Associated Types
| |||||
Generic GeneratedSecrets | |||||
Defined in Cardano.Chain.Genesis.Generate Associated Types
Methods from :: GeneratedSecrets -> Rep GeneratedSecrets x # to :: Rep GeneratedSecrets x -> GeneratedSecrets # | |||||
Generic PoorSecret | |||||
Defined in Cardano.Chain.Genesis.Generate Associated Types
| |||||
Generic GenesisHash | |||||
Defined in Cardano.Chain.Genesis.Hash Associated Types
| |||||
Generic FakeAvvmOptions | |||||
Defined in Cardano.Chain.Genesis.Initializer Associated Types
Methods from :: FakeAvvmOptions -> Rep FakeAvvmOptions x # to :: Rep FakeAvvmOptions x -> FakeAvvmOptions # | |||||
Generic GenesisSpec | |||||
Defined in Cardano.Chain.Genesis.Spec Associated Types
| |||||
Generic EpochAndSlotCount | |||||
Defined in Cardano.Chain.Slotting.EpochAndSlotCount Associated Types
Methods from :: EpochAndSlotCount -> Rep EpochAndSlotCount x # to :: Rep EpochAndSlotCount x -> EpochAndSlotCount # | |||||
Generic EpochNumber | |||||
Defined in Cardano.Chain.Slotting.EpochNumber Associated Types
| |||||
Generic EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Associated Types
| |||||
Generic SlotCount | |||||
Defined in Cardano.Chain.Slotting.SlotCount Associated Types
| |||||
Generic SlotNumber | |||||
Defined in Cardano.Chain.Slotting.SlotNumber Associated Types
| |||||
Generic SscPayload | |||||
Defined in Cardano.Chain.Ssc Associated Types
| |||||
Generic SscProof | |||||
Defined in Cardano.Chain.Ssc | |||||
Generic CompactTxId | |||||
Defined in Cardano.Chain.UTxO.Compact Associated Types
| |||||
Generic CompactTxIn | |||||
Defined in Cardano.Chain.UTxO.Compact Associated Types
| |||||
Generic CompactTxOut | |||||
Defined in Cardano.Chain.UTxO.Compact Associated Types
| |||||
Generic Tx | |||||
Defined in Cardano.Chain.UTxO.Tx Associated Types
| |||||
Generic TxIn | |||||
Defined in Cardano.Chain.UTxO.Tx Associated Types
| |||||
Generic TxOut | |||||
Defined in Cardano.Chain.UTxO.Tx Associated Types
| |||||
Generic TxProof | |||||
Defined in Cardano.Chain.UTxO.TxProof Associated Types
| |||||
Generic TxInWitness | |||||
Defined in Cardano.Chain.UTxO.TxWitness Associated Types
| |||||
Generic TxSigData | |||||
Defined in Cardano.Chain.UTxO.TxWitness Associated Types
| |||||
Generic UTxO | |||||
Defined in Cardano.Chain.UTxO.UTxO Associated Types
| |||||
Generic UTxOConfiguration | |||||
Defined in Cardano.Chain.UTxO.UTxOConfiguration Associated Types
Methods from :: UTxOConfiguration -> Rep UTxOConfiguration x # to :: Rep UTxOConfiguration x -> UTxOConfiguration # | |||||
Generic ApplicationName | |||||
Defined in Cardano.Chain.Update.ApplicationName Associated Types
Methods from :: ApplicationName -> Rep ApplicationName x # to :: Rep ApplicationName x -> ApplicationName # | |||||
Generic InstallerHash | |||||
Defined in Cardano.Chain.Update.InstallerHash Associated Types
| |||||
Generic ProposalBody | |||||
Defined in Cardano.Chain.Update.Proposal Associated Types
| |||||
Generic ProtocolParameters | |||||
Defined in Cardano.Chain.Update.ProtocolParameters Associated Types
Methods from :: ProtocolParameters -> Rep ProtocolParameters x # to :: Rep ProtocolParameters x -> ProtocolParameters # | |||||
Generic ProtocolParametersUpdate | |||||
Defined in Cardano.Chain.Update.ProtocolParametersUpdate Associated Types
Methods from :: ProtocolParametersUpdate -> Rep ProtocolParametersUpdate x # to :: Rep ProtocolParametersUpdate x -> ProtocolParametersUpdate # | |||||
Generic ProtocolVersion | |||||
Defined in Cardano.Chain.Update.ProtocolVersion Associated Types
Methods from :: ProtocolVersion -> Rep ProtocolVersion x # to :: Rep ProtocolVersion x -> ProtocolVersion # | |||||
Generic SoftforkRule | |||||
Defined in Cardano.Chain.Update.SoftforkRule Associated Types
| |||||
Generic SoftwareVersion | |||||
Defined in Cardano.Chain.Update.SoftwareVersion Associated Types
Methods from :: SoftwareVersion -> Rep SoftwareVersion x # to :: Rep SoftwareVersion x -> SoftwareVersion # | |||||
Generic SystemTag | |||||
Defined in Cardano.Chain.Update.SystemTag Associated Types
| |||||
Generic CandidateProtocolUpdate | |||||
Defined in Cardano.Chain.Update.Validation.Endorsement Associated Types
Methods from :: CandidateProtocolUpdate -> Rep CandidateProtocolUpdate x # to :: Rep CandidateProtocolUpdate x -> CandidateProtocolUpdate # | |||||
Generic Endorsement | |||||
Defined in Cardano.Chain.Update.Validation.Endorsement Associated Types
| |||||
Generic State | |||||
Defined in Cardano.Chain.Update.Validation.Interface Associated Types
| |||||
Generic ApplicationVersion | |||||
Defined in Cardano.Chain.Update.Validation.Registration Associated Types
Methods from :: ApplicationVersion -> Rep ApplicationVersion x # to :: Rep ApplicationVersion x -> ApplicationVersion # | |||||
Generic ProtocolUpdateProposal | |||||
Defined in Cardano.Chain.Update.Validation.Registration Associated Types
Methods from :: ProtocolUpdateProposal -> Rep ProtocolUpdateProposal x # to :: Rep ProtocolUpdateProposal x -> ProtocolUpdateProposal # | |||||
Generic SoftwareUpdateProposal | |||||
Defined in Cardano.Chain.Update.Validation.Registration Associated Types
Methods from :: SoftwareUpdateProposal -> Rep SoftwareUpdateProposal x # to :: Rep SoftwareUpdateProposal x -> SoftwareUpdateProposal # | |||||
Generic Environment | |||||
Defined in Cardano.Chain.Update.Validation.Voting Associated Types
| |||||
Generic RegistrationEnvironment | |||||
Defined in Cardano.Chain.Update.Validation.Voting Associated Types
Methods from :: RegistrationEnvironment -> Rep RegistrationEnvironment x # to :: Rep RegistrationEnvironment x -> RegistrationEnvironment # | |||||
Generic ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Associated Types
| |||||
Generic GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic GovActionPurpose | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovActionPurpose -> Rep GovActionPurpose x # to :: Rep GovActionPurpose x -> GovActionPurpose # | |||||
Generic Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: DRepVotingThresholds -> Rep DRepVotingThresholds x # to :: Rep DRepVotingThresholds x -> DRepVotingThresholds # | |||||
Generic PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: PoolVotingThresholds -> Rep PoolVotingThresholds x # to :: Rep PoolVotingThresholds x -> PoolVotingThresholds # | |||||
Generic ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
Methods from :: ConwayDelegCert -> Rep ConwayDelegCert x # to :: Rep ConwayDelegCert x -> ConwayDelegCert # | |||||
Generic ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
| |||||
Generic Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
| |||||
Generic Addr | |||||
Defined in Cardano.Ledger.Address Associated Types
| |||||
Generic BootstrapAddress | |||||
Defined in Cardano.Ledger.Address Associated Types
Methods from :: BootstrapAddress -> Rep BootstrapAddress x # to :: Rep BootstrapAddress x -> BootstrapAddress # | |||||
Generic CompactAddr | |||||
Defined in Cardano.Ledger.Address Associated Types
| |||||
Generic RewardAccount | |||||
Defined in Cardano.Ledger.Address Associated Types
| |||||
Generic Withdrawals | |||||
Defined in Cardano.Ledger.Address Associated Types
| |||||
Generic ActiveSlotCoeff | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: ActiveSlotCoeff -> Rep ActiveSlotCoeff x # to :: Rep ActiveSlotCoeff x -> ActiveSlotCoeff # | |||||
Generic Anchor | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic BlocksMade | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic DnsName | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Globals | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Network | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: NonNegativeInterval -> Rep NonNegativeInterval x # to :: Rep NonNegativeInterval x -> NonNegativeInterval # | |||||
Generic Nonce | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Port | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic PositiveInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: PositiveInterval -> Rep PositiveInterval x # to :: Rep PositiveInterval x -> PositiveInterval # | |||||
Generic PositiveUnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: PositiveUnitInterval -> Rep PositiveUnitInterval x # to :: Rep PositiveUnitInterval x -> PositiveUnitInterval # | |||||
Generic ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Relation | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Seed | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic TxIx | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic Url | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic CommitteeAuthorization | |||||
Defined in Cardano.Ledger.CertState Associated Types
Methods from :: CommitteeAuthorization -> Rep CommitteeAuthorization x # to :: Rep CommitteeAuthorization x -> CommitteeAuthorization # | |||||
Generic FutureGenDeleg | |||||
Defined in Cardano.Ledger.CertState Associated Types
Methods from :: FutureGenDeleg -> Rep FutureGenDeleg x # to :: Rep FutureGenDeleg x -> FutureGenDeleg # | |||||
Generic InstantaneousRewards | |||||
Defined in Cardano.Ledger.CertState Associated Types
Methods from :: InstantaneousRewards -> Rep InstantaneousRewards x # to :: Rep InstantaneousRewards x -> InstantaneousRewards # | |||||
Generic Obligations | |||||
Defined in Cardano.Ledger.CertState Associated Types
| |||||
Generic Coin | |||||
Defined in Cardano.Ledger.Coin Associated Types
| |||||
Generic DeltaCoin | |||||
Defined in Cardano.Ledger.Coin Associated Types
| |||||
Generic PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert Associated Types
| |||||
Generic Ptr | |||||
Defined in Cardano.Ledger.Credential Associated Types
| |||||
Generic SlotNo32 | |||||
Defined in Cardano.Ledger.Credential Associated Types
| |||||
Generic StakeReference | |||||
Defined in Cardano.Ledger.Credential Associated Types
Methods from :: StakeReference -> Rep StakeReference x # to :: Rep StakeReference x -> StakeReference # | |||||
Generic DRep | |||||
Defined in Cardano.Ledger.DRep Associated Types
| |||||
Generic DRepState | |||||
Defined in Cardano.Ledger.DRep Associated Types
| |||||
Generic GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
Generic GenDelegs | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
Generic ScriptHash | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
Generic TxAuxDataHash | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
Generic BootstrapWitness | |||||
Defined in Cardano.Ledger.Keys.Bootstrap Associated Types
Methods from :: BootstrapWitness -> Rep BootstrapWitness x # to :: Rep BootstrapWitness x -> BootstrapWitness # | |||||
Generic BootstrapWitnessRaw | |||||
Defined in Cardano.Ledger.Keys.Bootstrap Associated Types
Methods from :: BootstrapWitnessRaw -> Rep BootstrapWitnessRaw x # to :: Rep BootstrapWitnessRaw x -> BootstrapWitnessRaw # | |||||
Generic ChainCode | |||||
Defined in Cardano.Ledger.Keys.Bootstrap Associated Types
| |||||
Generic Metadatum | |||||
Defined in Cardano.Ledger.Metadata Associated Types
| |||||
Generic CostModel | |||||
Defined in Cardano.Ledger.Plutus.CostModels Associated Types
| |||||
Generic CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Associated Types
| |||||
Generic ScriptFailure | |||||
Defined in Cardano.Ledger.Plutus.Evaluate Associated Types
| |||||
Generic ScriptResult | |||||
Defined in Cardano.Ledger.Plutus.Evaluate Associated Types
| |||||
Generic ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Associated Types
| |||||
Generic Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Associated Types
| |||||
Generic Language | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
| |||||
Generic PlutusBinary | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
| |||||
Generic TxOutSource | |||||
Defined in Cardano.Ledger.Plutus.TxInfo Associated Types
| |||||
Generic PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
| |||||
Generic PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
| |||||
Generic StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
Methods from :: StakePoolRelay -> Rep StakePoolRelay x # to :: Rep StakePoolRelay x -> StakePoolRelay # | |||||
Generic Reward | |||||
Defined in Cardano.Ledger.Rewards Associated Types
| |||||
Generic RewardType | |||||
Defined in Cardano.Ledger.Rewards Associated Types
| |||||
Generic Duration | |||||
Defined in Cardano.Ledger.Slot Associated Types
| |||||
Generic AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Associated Types
| |||||
Generic IndividualPoolStake | |||||
Defined in Cardano.Ledger.State.PoolDistr Associated Types
Methods from :: IndividualPoolStake -> Rep IndividualPoolStake x # to :: Rep IndividualPoolStake x -> IndividualPoolStake # | |||||
Generic PoolDistr | |||||
Defined in Cardano.Ledger.State.PoolDistr Associated Types
| |||||
Generic SnapShot | |||||
Defined in Cardano.Ledger.State.SnapShots Associated Types
| |||||
Generic SnapShots | |||||