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 | |||||
Defined in Cardano.Ledger.State.SnapShots Associated Types
| |||||
Generic Stake | |||||
Defined in Cardano.Ledger.State.SnapShots Associated Types
| |||||
Generic TxId | |||||
Defined in Cardano.Ledger.TxIn Associated Types
| |||||
Generic TxIn | |||||
Defined in Cardano.Ledger.TxIn Associated Types
| |||||
Generic RDPair | |||||
Defined in Cardano.Ledger.UMap Associated Types
| |||||
Generic StakeCredentials | |||||
Defined in Cardano.Ledger.UMap Associated Types
Methods from :: StakeCredentials -> Rep StakeCredentials x # to :: Rep StakeCredentials x -> StakeCredentials # | |||||
Generic UMElem | |||||
Defined in Cardano.Ledger.UMap Associated Types
| |||||
Generic UMap | |||||
Defined in Cardano.Ledger.UMap Associated Types
| |||||
Generic ByronKeyPair | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Associated Types
| |||||
Generic PlutusArgs | |||||
Defined in Test.Cardano.Ledger.Plutus.ScriptTestContext Associated Types
| |||||
Generic CompactValue | |||||
Defined in Cardano.Ledger.Mary.Value Associated Types
| |||||
Generic MaryValue | |||||
Defined in Cardano.Ledger.Mary.Value Associated Types
| |||||
Generic MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Associated Types
| |||||
Generic PolicyID | |||||
Defined in Cardano.Ledger.Mary.Value Associated Types
| |||||
Generic ChainChecksPParams | |||||
Defined in Cardano.Ledger.Chain Associated Types
Methods from :: ChainChecksPParams -> Rep ChainChecksPParams x # to :: Rep ChainChecksPParams x -> ChainChecksPParams # | |||||
Generic ChainPredicateFailure | |||||
Defined in Cardano.Ledger.Chain Associated Types
Methods from :: ChainPredicateFailure -> Rep ChainPredicateFailure x # to :: Rep ChainPredicateFailure x -> ChainPredicateFailure # | |||||
Generic RewardInfoPool | |||||
Defined in Cardano.Ledger.Shelley.API.Wallet Associated Types
Methods from :: RewardInfoPool -> Rep RewardInfoPool x # to :: Rep RewardInfoPool x -> RewardInfoPool # | |||||
Generic RewardParams | |||||
Defined in Cardano.Ledger.Shelley.API.Wallet Associated Types
| |||||
Generic AdaPots | |||||
Defined in Cardano.Ledger.Shelley.AdaPots Associated Types
| |||||
Generic NominalDiffTimeMicro | |||||
Defined in Cardano.Ledger.Shelley.Genesis Associated Types
Methods from :: NominalDiffTimeMicro -> Rep NominalDiffTimeMicro x # to :: Rep NominalDiffTimeMicro x -> NominalDiffTimeMicro # | |||||
Generic ShelleyGenesis | |||||
Defined in Cardano.Ledger.Shelley.Genesis Associated Types
Methods from :: ShelleyGenesis -> Rep ShelleyGenesis x # to :: Rep ShelleyGenesis x -> ShelleyGenesis # | |||||
Generic ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Associated Types
Methods from :: ShelleyGenesisStaking -> Rep ShelleyGenesisStaking x # to :: Rep ShelleyGenesisStaking x -> ShelleyGenesisStaking # | |||||
Generic PPUpdateEnv | |||||
Defined in Cardano.Ledger.Shelley.PParams Associated Types
| |||||
Generic Histogram | |||||
Defined in Cardano.Ledger.Shelley.PoolRank Associated Types
| |||||
Generic Likelihood | |||||
Defined in Cardano.Ledger.Shelley.PoolRank Associated Types
| |||||
Generic LogWeight | |||||
Defined in Cardano.Ledger.Shelley.PoolRank Associated Types
| |||||
Generic NonMyopic | |||||
Defined in Cardano.Ledger.Shelley.PoolRank Associated Types
| |||||
Generic PerformanceEstimate | |||||
Defined in Cardano.Ledger.Shelley.PoolRank Associated Types
Methods from :: PerformanceEstimate -> Rep PerformanceEstimate x # to :: Rep PerformanceEstimate x -> PerformanceEstimate # | |||||
Generic Desirability | |||||
Defined in Cardano.Ledger.Shelley.RewardProvenance Associated Types
| |||||
Generic RewardProvenance | |||||
Defined in Cardano.Ledger.Shelley.RewardProvenance Associated Types
Methods from :: RewardProvenance -> Rep RewardProvenance x # to :: Rep RewardProvenance x -> RewardProvenance # | |||||
Generic RewardProvenancePool | |||||
Defined in Cardano.Ledger.Shelley.RewardProvenance Associated Types
Methods from :: RewardProvenancePool -> Rep RewardProvenancePool x # to :: Rep RewardProvenancePool x -> RewardProvenancePool # | |||||
Generic FreeVars | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
| |||||
Generic PulsingRewUpdate | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
Methods from :: PulsingRewUpdate -> Rep PulsingRewUpdate x # to :: Rep PulsingRewUpdate x -> PulsingRewUpdate # | |||||
Generic RewardAns | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
| |||||
Generic RewardSnapShot | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
Methods from :: RewardSnapShot -> Rep RewardSnapShot x # to :: Rep RewardSnapShot x -> RewardSnapShot # | |||||
Generic RewardUpdate | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
| |||||
Generic LeaderOnlyReward | |||||
Defined in Cardano.Ledger.Shelley.Rewards Associated Types
Methods from :: LeaderOnlyReward -> Rep LeaderOnlyReward x # to :: Rep LeaderOnlyReward x -> LeaderOnlyReward # | |||||
Generic PoolRewardInfo | |||||
Defined in Cardano.Ledger.Shelley.Rewards Associated Types
Methods from :: PoolRewardInfo -> Rep PoolRewardInfo x # to :: Rep PoolRewardInfo x -> PoolRewardInfo # | |||||
Generic StakeShare | |||||
Defined in Cardano.Ledger.Shelley.Rewards Associated Types
| |||||
Generic VotingPeriod | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
| |||||
Generic RupdEvent | |||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd Associated Types
| |||||
Generic FromByronTranslationContext | |||||
Defined in Cardano.Ledger.Shelley.Translation Associated Types
Methods from :: FromByronTranslationContext -> Rep FromByronTranslationContext x # to :: Rep FromByronTranslationContext x -> FromByronTranslationContext # | |||||
Generic GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: GenesisDelegCert -> Rep GenesisDelegCert x # to :: Rep GenesisDelegCert x -> GenesisDelegCert # | |||||
Generic MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Generic MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Generic MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Generic ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: ShelleyDelegCert -> Rep ShelleyDelegCert x # to :: Rep ShelleyDelegCert x -> ShelleyDelegCert # | |||||
Generic NCForkPolicy | |||||
Defined in Cardano.Node.Configuration.POM Associated Types
| |||||
Generic NetworkP2PMode | |||||
Defined in Cardano.Node.Configuration.POM Associated Types
Methods from :: NetworkP2PMode -> Rep NetworkP2PMode x # to :: Rep NetworkP2PMode x -> NetworkP2PMode # | |||||
Generic PartialNodeConfiguration | |||||
Defined in Cardano.Node.Configuration.POM Associated Types
Methods from :: PartialNodeConfiguration -> Rep PartialNodeConfiguration x # to :: Rep PartialNodeConfiguration x -> PartialNodeConfiguration # | |||||
Generic ShutdownOn | |||||
Defined in Cardano.Node.Handlers.Shutdown Associated Types
| |||||
Generic ShutdownTrace | |||||
Defined in Cardano.Node.Handlers.Shutdown Associated Types
| |||||
Generic Protocol | |||||
Defined in Cardano.Node.Protocol.Types | |||||
Generic NodeInfo | |||||
Defined in Cardano.Node.Startup Associated Types
| |||||
Generic NodeStartupInfo | |||||
Defined in Cardano.Node.Startup Associated Types
Methods from :: NodeStartupInfo -> Rep NodeStartupInfo x # to :: Rep NodeStartupInfo x -> NodeStartupInfo # | |||||
Generic PartialTraceSelection | |||||
Defined in Cardano.Tracing.Config Associated Types
Methods from :: PartialTraceSelection -> Rep PartialTraceSelection x # to :: Rep PartialTraceSelection x -> PartialTraceSelection # | |||||
Generic InitiatorOnly | |||||
Defined in Cardano.Network.Ping Associated Types
| |||||
Generic PeerSharing | |||||
Defined in Cardano.Network.Ping Associated Types
| |||||
Generic ChainDepState | |||||
Defined in Cardano.Protocol.TPraos.API Associated Types
| |||||
Generic LedgerView | |||||
Defined in Cardano.Protocol.TPraos.API Associated Types
| |||||
Generic HashHeader | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
| |||||
Generic LastAppliedBlock | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
Methods from :: LastAppliedBlock -> Rep LastAppliedBlock x # to :: Rep LastAppliedBlock x -> LastAppliedBlock # | |||||
Generic PrevHash | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
| |||||
Generic KESPeriod | |||||
Defined in Cardano.Protocol.TPraos.OCert Associated Types
| |||||
Generic OcertPredicateFailure | |||||
Defined in Cardano.Protocol.TPraos.Rules.OCert Associated Types
Methods from :: OcertPredicateFailure -> Rep OcertPredicateFailure x # to :: Rep OcertPredicateFailure x -> OcertPredicateFailure # | |||||
Generic OBftSlot | |||||
Defined in Cardano.Protocol.TPraos.Rules.Overlay Associated Types
| |||||
Generic OverlayEnv | |||||
Defined in Cardano.Protocol.TPraos.Rules.Overlay Associated Types
| |||||
Generic PrtclEnv | |||||
Defined in Cardano.Protocol.TPraos.Rules.Prtcl Associated Types
| |||||
Generic PrtclState | |||||
Defined in Cardano.Protocol.TPraos.Rules.Prtcl Associated Types
| |||||
Generic PrtlSeqFailure | |||||
Defined in Cardano.Protocol.TPraos.Rules.Prtcl Associated Types
Methods from :: PrtlSeqFailure -> Rep PrtlSeqFailure x # to :: Rep PrtlSeqFailure x -> PrtlSeqFailure # | |||||
Generic TicknPredicateFailure | |||||
Defined in Cardano.Protocol.TPraos.Rules.Tickn Associated Types
Methods from :: TicknPredicateFailure -> Rep TicknPredicateFailure x # to :: Rep TicknPredicateFailure x -> TicknPredicateFailure # | |||||
Generic TicknState | |||||
Defined in Cardano.Protocol.TPraos.Rules.Tickn Associated Types
| |||||
Generic BlockNo | |||||
Defined in Cardano.Slotting.Block Associated Types
| |||||
Generic EpochInterval | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Generic EpochNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Generic EpochSize | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Generic SlotNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Generic RelativeTime | |||||
Defined in Cardano.Slotting.Time Associated Types
| |||||
Generic SlotLength | |||||
Defined in Cardano.Slotting.Time Associated Types
| |||||
Generic SystemStart | |||||
Defined in Cardano.Slotting.Time Associated Types
| |||||
Generic LeadershipSlot | |||||
Defined in Testnet.Types Associated Types
Methods from :: LeadershipSlot -> Rep LeadershipSlot x # to :: Rep LeadershipSlot x -> LeadershipSlot # | |||||
Generic Slot | |||||
Defined in Clb.TimeSlot Associated Types
| |||||
Generic SlotConfig | |||||
Defined in Clb.TimeSlot Associated Types
| |||||
Generic Clock | |||||
Defined in System.Clock Associated Types
| |||||
Generic TimeSpec | |||||
Defined in System.Clock Associated Types
| |||||
Generic FileType | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Generic SymlinkType | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Generic MetricValue | |||||
Defined in System.Metrics.ReqResp Associated Types
| |||||
Generic Request | |||||
Defined in System.Metrics.ReqResp Associated Types
| |||||
Generic Response | |||||
Defined in System.Metrics.ReqResp Associated Types
| |||||
Generic Filler | |||||
Defined in Flat.Filler Associated Types
| |||||
Generic FsPath | |||||
Defined in System.FS.API.Types Associated Types
| |||||
Generic CRC | |||||
Defined in System.FS.CRC Associated Types
| |||||
Generic ForeignSrcLang | |||||
Defined in GHC.ForeignSrcLang.Type Associated Types
Methods from :: ForeignSrcLang -> Rep ForeignSrcLang x # to :: Rep ForeignSrcLang x -> ForeignSrcLang # | |||||
Generic Extension | |||||
Defined in GHC.LanguageExtensions.Type Associated Types
| |||||
Generic PrimType | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
| |||||
Generic TsoFlags | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
| |||||
Generic WhatNext | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
| |||||
Generic WhyBlocked | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
| |||||
Generic StgInfoTable | |||||
Defined in GHC.Exts.Heap.InfoTable.Types Associated Types
| |||||
Generic CostCentre | |||||
Defined in GHC.Exts.Heap.ProfInfo.Types Associated Types
| |||||
Generic CostCentreStack | |||||
Defined in GHC.Exts.Heap.ProfInfo.Types Associated Types
Methods from :: CostCentreStack -> Rep CostCentreStack x # to :: Rep CostCentreStack x -> CostCentreStack # | |||||
Generic IndexTable | |||||
Defined in GHC.Exts.Heap.ProfInfo.Types Associated Types
| |||||
Generic StgTSOProfInfo | |||||
Defined in GHC.Exts.Heap.ProfInfo.Types Associated Types
Methods from :: StgTSOProfInfo -> Rep StgTSOProfInfo x # to :: Rep StgTSOProfInfo x -> StgTSOProfInfo # | |||||
Generic Void | |||||
Generic ByteOrder | |||||
Defined in GHC.Internal.ByteOrder | |||||
Generic ClosureType | |||||
Defined in GHC.Internal.ClosureTypes Associated Types
| |||||
Generic All | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic Any | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic Version | |||||
Defined in GHC.Internal.Data.Version Associated Types
| |||||
Generic Fingerprint | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic Associativity | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic DecidedStrictness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic Fixity | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic SourceStrictness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic ExitCode | |||||
Defined in GHC.Internal.IO.Exception Associated Types
| |||||
Generic CCFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ConcFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DebugFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoCostCentres | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoHeapProfile | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic DoTrace | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic GCFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic GiveGCStats | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic HpcFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic MiscFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ParFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic ProfFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic RTSFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic TickyFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic TraceFlags | |||||
Defined in GHC.Internal.RTS.Flags Associated Types
| |||||
Generic SrcLoc | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic GCDetails | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
Generic RTSStats | |||||
Defined in GHC.Internal.Stats Associated Types
| |||||
Generic GeneralCategory | |||||
Defined in GHC.Internal.Generics Associated Types
Methods from :: GeneralCategory -> Rep GeneralCategory x # to :: Rep GeneralCategory x -> GeneralCategory # | |||||
Generic Ordering | |||||
Defined in GHC.Internal.Generics | |||||
Generic Half | |||||
Defined in Numeric.Half.Internal Associated Types
| |||||
Generic Component | |||||
Defined in Hedgehog.Extras.Internal.Plan Associated Types
| |||||
Generic Plan | |||||
Defined in Hedgehog.Extras.Internal.Plan Associated Types
| |||||
Generic IntegrationState | |||||
Defined in Hedgehog.Extras.Internal.Test.Integration Associated Types
Methods from :: IntegrationState -> Rep IntegrationState x # to :: Rep IntegrationState x -> IntegrationState # | |||||
Generic Sprocket | |||||
Defined in Hedgehog.Extras.Stock.IO.Network.Sprocket Associated Types
| |||||
Generic TimedOut | |||||
Defined in Hedgehog.Extras.Stock.IO.Process | |||||
Generic ExecConfig | |||||
Defined in Hedgehog.Extras.Test.Process Associated Types
| |||||
Generic Form | |||||
Defined in Web.Internal.FormUrlEncoded Associated Types
| |||||
Generic ByteRange | |||||
Defined in Network.HTTP.Types.Header Associated Types
| |||||
Generic StdMethod | |||||
Defined in Network.HTTP.Types.Method Associated Types
| |||||
Generic Status | |||||
Defined in Network.HTTP.Types.Status Associated Types
| |||||
Generic HttpVersion | |||||
Defined in Network.HTTP.Types.Version Associated Types
| |||||
Generic Aggregated | |||||
Defined in Cardano.BM.Data.Aggregated Associated Types
| |||||
Generic BaseStats | |||||
Defined in Cardano.BM.Data.Aggregated Associated Types
| |||||
Generic EWMA | |||||
Defined in Cardano.BM.Data.Aggregated Associated Types
| |||||
Generic Measurable | |||||
Defined in Cardano.BM.Data.Aggregated Associated Types
| |||||
Generic Stats | |||||
Defined in Cardano.BM.Data.Aggregated Associated Types
| |||||
Generic AggregatedKind | |||||
Defined in Cardano.BM.Data.AggregatedKind Associated Types
Methods from :: AggregatedKind -> Rep AggregatedKind x # to :: Rep AggregatedKind x -> AggregatedKind # | |||||
Generic Endpoint | |||||
Defined in Cardano.BM.Data.Configuration Associated Types
| |||||
Generic RemoteAddr | |||||
Defined in Cardano.BM.Data.Configuration Associated Types
| |||||
Generic RemoteAddrNamed | |||||
Defined in Cardano.BM.Data.Configuration Associated Types
Methods from :: RemoteAddrNamed -> Rep RemoteAddrNamed x # to :: Rep RemoteAddrNamed x -> RemoteAddrNamed # | |||||
Generic Representation | |||||
Defined in Cardano.BM.Data.Configuration Associated Types
Methods from :: Representation -> Rep Representation x # to :: Rep Representation x -> Representation # | |||||
Generic Counter | |||||
Defined in Cardano.BM.Data.Counter Associated Types
| |||||
Generic CounterState | |||||
Defined in Cardano.BM.Data.Counter Associated Types
| |||||
Generic CounterType | |||||
Defined in Cardano.BM.Data.Counter Associated Types
| |||||
Generic ObservableInstance | |||||
Defined in Cardano.BM.Data.Observable Associated Types
Methods from :: ObservableInstance -> Rep ObservableInstance x # to :: Rep ObservableInstance x -> ObservableInstance # | |||||
Generic ScribeDefinition | |||||
Defined in Cardano.BM.Data.Output Associated Types
Methods from :: ScribeDefinition -> Rep ScribeDefinition x # to :: Rep ScribeDefinition x -> ScribeDefinition # | |||||
Generic ScribeFormat | |||||
Defined in Cardano.BM.Data.Output Associated Types
| |||||
Generic ScribeKind | |||||
Defined in Cardano.BM.Data.Output Associated Types
| |||||
Generic ScribePrivacy | |||||
Defined in Cardano.BM.Data.Output Associated Types
| |||||
Generic RotationParameters | |||||
Defined in Cardano.BM.Data.Rotation Associated Types
Methods from :: RotationParameters -> Rep RotationParameters x # to :: Rep RotationParameters x -> RotationParameters # | |||||
Generic Severity | |||||
Defined in Cardano.BM.Data.Severity Associated Types
| |||||
Generic DropName | |||||
Defined in Cardano.BM.Data.SubTrace Associated Types
| |||||
Generic NameSelector | |||||
Defined in Cardano.BM.Data.SubTrace Associated Types
| |||||
Generic SubTrace | |||||
Defined in Cardano.BM.Data.SubTrace Associated Types
| |||||
Generic UnhideNames | |||||
Defined in Cardano.BM.Data.SubTrace Associated Types
| |||||
Generic IP | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPv4 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPv6 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
Generic IPRange | |||||
Defined in Data.IP.Range Associated Types
| |||||
Generic Environment | |||||
Defined in Katip.Core Associated Types
| |||||
Generic LogStr | |||||
Defined in Katip.Core Associated Types
| |||||
Generic Namespace | |||||
Defined in Katip.Core Associated Types
| |||||
Generic Severity | |||||
Defined in Katip.Core Associated Types
| |||||
Generic Verbosity | |||||
Defined in Katip.Core Associated Types
| |||||
Generic ApiError | |||||
Defined in Maestro.Client.Error Associated Types
| |||||
Generic AbsoluteSlot | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic BlockHash | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic BlockHeight | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic DatumOption | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic DatumOptionType | |||||
Defined in Maestro.Types.Common Associated Types
Methods from :: DatumOptionType -> Rep DatumOptionType x # to :: Rep DatumOptionType x -> DatumOptionType # | |||||
Generic EpochNo | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic EpochSize | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic PolicyId | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic Script | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic ScriptType | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic SlotNo | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic TokenName | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic TxHash | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic TxIndex | |||||
Defined in Maestro.Types.Common Associated Types
| |||||
Generic AccountAction | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
| |||||
Generic AccountHistory | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: AccountHistory -> Rep AccountHistory x # to :: Rep AccountHistory x -> AccountHistory # | |||||
Generic AccountInfo | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
| |||||
Generic AccountReward | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
| |||||
Generic AccountStakingRewardType | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: AccountStakingRewardType -> Rep AccountStakingRewardType x # to :: Rep AccountStakingRewardType x -> AccountStakingRewardType # | |||||
Generic AccountUpdate | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
| |||||
Generic PaginatedAccountHistory | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: PaginatedAccountHistory -> Rep PaginatedAccountHistory x # to :: Rep PaginatedAccountHistory x -> PaginatedAccountHistory # | |||||
Generic PaginatedAccountReward | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: PaginatedAccountReward -> Rep PaginatedAccountReward x # to :: Rep PaginatedAccountReward x -> PaginatedAccountReward # | |||||
Generic PaginatedAccountUpdate | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: PaginatedAccountUpdate -> Rep PaginatedAccountUpdate x # to :: Rep PaginatedAccountUpdate x -> PaginatedAccountUpdate # | |||||
Generic PaginatedAddress | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: PaginatedAddress -> Rep PaginatedAddress x # to :: Rep PaginatedAddress x -> PaginatedAddress # | |||||
Generic PaginatedAsset | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: PaginatedAsset -> Rep PaginatedAsset x # to :: Rep PaginatedAsset x -> PaginatedAsset # | |||||
Generic TimestampedAccountInfo | |||||
Defined in Maestro.Types.V1.Accounts Associated Types
Methods from :: TimestampedAccountInfo -> Rep TimestampedAccountInfo x # to :: Rep TimestampedAccountInfo x -> TimestampedAccountInfo # | |||||
Generic AddressInfo | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic AddressTransaction | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: AddressTransaction -> Rep AddressTransaction x # to :: Rep AddressTransaction x -> AddressTransaction # | |||||
Generic CertIndex | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic ChainPointer | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic NetworkId | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic OutputReferenceObject | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: OutputReferenceObject -> Rep OutputReferenceObject x # to :: Rep OutputReferenceObject x -> OutputReferenceObject # | |||||
Generic PaginatedAddressTransaction | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: PaginatedAddressTransaction -> Rep PaginatedAddressTransaction x # to :: Rep PaginatedAddressTransaction x -> PaginatedAddressTransaction # | |||||
Generic PaginatedOutputReferenceObject | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic PaginatedPaymentCredentialTransaction | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic PaymentCredKind | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: PaymentCredKind -> Rep PaymentCredKind x # to :: Rep PaymentCredKind x -> PaymentCredKind # | |||||
Generic PaymentCredential | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: PaymentCredential -> Rep PaymentCredential x # to :: Rep PaymentCredential x -> PaymentCredential # | |||||
Generic PaymentCredentialTransaction | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
| |||||
Generic StakingCredKind | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: StakingCredKind -> Rep StakingCredKind x # to :: Rep StakingCredKind x -> StakingCredKind # | |||||
Generic StakingCredential | |||||
Defined in Maestro.Types.V1.Addresses Associated Types
Methods from :: StakingCredential -> Rep StakingCredential x # to :: Rep StakingCredential x -> StakingCredential # | |||||
Generic AssetInfo | |||||
Defined in Maestro.Types.V1.Assets Associated Types
| |||||
Generic AssetStandards | |||||
Defined in Maestro.Types.V1.Assets Associated Types
| |||||
Generic AssetUTxOs | |||||
Defined in Maestro.Types.V1.Assets Associated Types
| |||||
Generic Cip68AssetType | |||||
Defined in Maestro.Types.V1.Assets Associated Types
| |||||
Generic Cip68Metadata | |||||
Defined in Maestro.Types.V1.Assets Associated Types
| |||||
Generic TimestampedAssetInfo | |||||
Defined in Maestro.Types.V1.Assets Associated Types
Methods from :: TimestampedAssetInfo -> Rep TimestampedAssetInfo x # to :: Rep TimestampedAssetInfo x -> TimestampedAssetInfo # | |||||
Generic TimestampedAssetUTxOs | |||||
Defined in Maestro.Types.V1.Assets Associated Types
Methods from :: TimestampedAssetUTxOs -> Rep TimestampedAssetUTxOs x # to :: Rep TimestampedAssetUTxOs x -> TimestampedAssetUTxOs # | |||||
Generic TokenRegistryMetadata | |||||
Defined in Maestro.Types.V1.Assets Associated Types
Methods from :: TokenRegistryMetadata -> Rep TokenRegistryMetadata x # to :: Rep TokenRegistryMetadata x -> TokenRegistryMetadata # | |||||
Generic BlockDetails | |||||
Defined in Maestro.Types.V1.Blocks Associated Types
| |||||
Generic TimestampedBlockDetails | |||||
Defined in Maestro.Types.V1.Blocks Associated Types
Methods from :: TimestampedBlockDetails -> Rep TimestampedBlockDetails x # to :: Rep TimestampedBlockDetails x -> TimestampedBlockDetails # | |||||
Generic Asset | |||||
Defined in Maestro.Types.V1.Common Associated Types
| |||||
Generic PaginatedUtxoWithSlot | |||||
Defined in Maestro.Types.V1.Common Associated Types
Methods from :: PaginatedUtxoWithSlot -> Rep PaginatedUtxoWithSlot x # to :: Rep PaginatedUtxoWithSlot x -> PaginatedUtxoWithSlot # | |||||
Generic UtxoWithSlot | |||||
Defined in Maestro.Types.V1.Common Associated Types
| |||||
Generic NextCursor | |||||
Defined in Maestro.Types.V1.Common.Pagination Associated Types
| |||||
Generic LastUpdated | |||||
Defined in Maestro.Types.V1.Common.Timestamped Associated Types
| |||||
Generic Datum | |||||
Defined in Maestro.Types.V1.Datum Associated Types
| |||||
Generic TimestampedDatum | |||||
Defined in Maestro.Types.V1.Datum Associated Types
Methods from :: TimestampedDatum -> Rep TimestampedDatum x # to :: Rep TimestampedDatum x -> TimestampedDatum # | |||||
Generic Dex | |||||
Defined in Maestro.Types.V1.DefiMarkets Associated Types
| |||||
Generic DexPairInfo | |||||
Defined in Maestro.Types.V1.DefiMarkets Associated Types
| |||||
Generic DexPairResponse | |||||
Defined in Maestro.Types.V1.DefiMarkets Associated Types
Methods from :: DexPairResponse -> Rep DexPairResponse x # to :: Rep DexPairResponse x -> DexPairResponse # | |||||
Generic OHLCCandleInfo | |||||
Defined in Maestro.Types.V1.DefiMarkets Associated Types
Methods from :: OHLCCandleInfo -> Rep OHLCCandleInfo x # to :: Rep OHLCCandleInfo x -> OHLCCandleInfo # | |||||
Generic Resolution | |||||
Defined in Maestro.Types.V1.DefiMarkets Associated Types
| |||||
Generic AsAda | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic AsBytes | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic AsLovelace | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic ChainTip | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic ConstitutionalCommittee | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: ConstitutionalCommittee -> Rep ConstitutionalCommittee x # to :: Rep ConstitutionalCommittee x -> ConstitutionalCommittee # | |||||
Generic CostModels | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic DRepVotingThresholds | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: DRepVotingThresholds -> Rep DRepVotingThresholds x # to :: Rep DRepVotingThresholds x -> DRepVotingThresholds # | |||||
Generic EpochSlotLength | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: EpochSlotLength -> Rep EpochSlotLength x # to :: Rep EpochSlotLength x -> EpochSlotLength # | |||||
Generic EraBound | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic EraBoundTime | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic EraParameters | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic EraSummary | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic MinFeeReferenceScripts | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: MinFeeReferenceScripts -> Rep MinFeeReferenceScripts x # to :: Rep MinFeeReferenceScripts x -> MinFeeReferenceScripts # | |||||
Generic ProtocolParameters | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: ProtocolParameters -> Rep ProtocolParameters x # to :: Rep ProtocolParameters x -> ProtocolParameters # | |||||
Generic ProtocolParametersUpdateDRep | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic ProtocolParametersUpdateStakePool | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic ProtocolVersion | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: ProtocolVersion -> Rep ProtocolVersion x # to :: Rep ProtocolVersion x -> ProtocolVersion # | |||||
Generic StakePoolVotingThresholds | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: StakePoolVotingThresholds -> Rep StakePoolVotingThresholds x # to :: Rep StakePoolVotingThresholds x -> StakePoolVotingThresholds # | |||||
Generic TimestampedChainTip | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: TimestampedChainTip -> Rep TimestampedChainTip x # to :: Rep TimestampedChainTip x -> TimestampedChainTip # | |||||
Generic TimestampedEraSummaries | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: TimestampedEraSummaries -> Rep TimestampedEraSummaries x # to :: Rep TimestampedEraSummaries x -> TimestampedEraSummaries # | |||||
Generic TimestampedProtocolParameters | |||||
Defined in Maestro.Types.V1.General Associated Types
| |||||
Generic TimestampedSystemStart | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: TimestampedSystemStart -> Rep TimestampedSystemStart x # to :: Rep TimestampedSystemStart x -> TimestampedSystemStart # | |||||
Generic PaginatedPoolListInfo | |||||
Defined in Maestro.Types.V1.Pools Associated Types
Methods from :: PaginatedPoolListInfo -> Rep PaginatedPoolListInfo x # to :: Rep PaginatedPoolListInfo x -> PaginatedPoolListInfo # | |||||
Generic PoolListInfo | |||||
Defined in Maestro.Types.V1.Pools Associated Types
| |||||
Generic PaginatedUtxo | |||||
Defined in Maestro.Types.V1.Transactions Associated Types
| |||||
Generic TimestampedTxDetails | |||||
Defined in Maestro.Types.V1.Transactions Associated Types
Methods from :: TimestampedTxDetails -> Rep TimestampedTxDetails x # to :: Rep TimestampedTxDetails x -> TimestampedTxDetails # | |||||
Generic TxDetails | |||||
Defined in Maestro.Types.V1.Transactions Associated Types
| |||||
Generic UtxoWithBytes | |||||
Defined in Maestro.Types.V1.Transactions Associated Types
| |||||
Generic NewtonParam | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic NewtonStep | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic RiddersParam | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic RiddersStep | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic Tolerance | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Associated Types
Methods from :: InvalidPosException -> Rep InvalidPosException x # to :: Rep InvalidPosException x -> InvalidPosException # | |||||
Generic Pos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
Generic SourcePos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
Generic SDUSize | |||||
Defined in Network.Mux.Types Associated Types
| |||||
Generic URI | |||||
Defined in Network.URI Associated Types
| |||||
Generic URIAuth | |||||
Defined in Network.URI Associated Types
| |||||
Generic ApiKeyLocation | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: ApiKeyLocation -> Rep ApiKeyLocation x # to :: Rep ApiKeyLocation x -> ApiKeyLocation # | |||||
Generic ApiKeyParams | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Callback | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Components | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Contact | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Discriminator | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Encoding | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Example | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic ExpressionOrValue | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: ExpressionOrValue -> Rep ExpressionOrValue x # to :: Rep ExpressionOrValue x -> ExpressionOrValue # | |||||
Generic ExternalDocs | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Header | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic HttpSchemeType | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: HttpSchemeType -> Rep HttpSchemeType x # to :: Rep HttpSchemeType x -> HttpSchemeType # | |||||
Generic Info | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic License | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Link | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic MediaTypeObject | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: MediaTypeObject -> Rep MediaTypeObject x # to :: Rep MediaTypeObject x -> MediaTypeObject # | |||||
Generic NamedSchema | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic OAuth2AuthorizationCodeFlow | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x # to :: Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow # | |||||
Generic OAuth2ClientCredentialsFlow | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x # to :: Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow # | |||||
Generic OAuth2Flows | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic OAuth2ImplicitFlow | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x # to :: Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow # | |||||
Generic OAuth2PasswordFlow | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x # to :: Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow # | |||||
Generic OpenApi | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic OpenApiSpecVersion | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: OpenApiSpecVersion -> Rep OpenApiSpecVersion x # to :: Rep OpenApiSpecVersion x -> OpenApiSpecVersion # | |||||
Generic OpenApiType | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Operation | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Param | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic ParamLocation | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic PathItem | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic RequestBody | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Response | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Responses | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Schema | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic SecurityDefinitions | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: SecurityDefinitions -> Rep SecurityDefinitions x # to :: Rep SecurityDefinitions x -> SecurityDefinitions # | |||||
Generic SecurityScheme | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: SecurityScheme -> Rep SecurityScheme x # to :: Rep SecurityScheme x -> SecurityScheme # | |||||
Generic SecuritySchemeType | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: SecuritySchemeType -> Rep SecuritySchemeType x # to :: Rep SecuritySchemeType x -> SecuritySchemeType # | |||||
Generic Server | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic ServerVariable | |||||
Defined in Data.OpenApi.Internal Associated Types
Methods from :: ServerVariable -> Rep ServerVariable x # to :: Rep ServerVariable x -> ServerVariable # | |||||
Generic Style | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Tag | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic Xml | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic OsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic OsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic PosixChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic PosixString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic WindowsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
Generic IsEBB | |||||
Defined in Ouroboros.Consensus.Block.EBB Associated Types
| |||||
Generic CurrentSlot | |||||
Defined in Ouroboros.Consensus.BlockchainTime.API Associated Types
| |||||
Generic SecurityParam | |||||
Defined in Ouroboros.Consensus.Config.SecurityParam Associated Types
| |||||
Generic EraMismatch | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Associated Types
| |||||
Generic Past | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types Associated Types
| |||||
Generic TransitionInfo | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types Associated Types
Methods from :: TransitionInfo -> Rep TransitionInfo x # to :: Rep TransitionInfo x -> TransitionInfo # | |||||
Generic EraParams | |||||
Defined in Ouroboros.Consensus.HardFork.History.EraParams Associated Types
| |||||
Generic SafeZone | |||||
Defined in Ouroboros.Consensus.HardFork.History.EraParams Associated Types
| |||||
Generic EpochInEra | |||||
Defined in Ouroboros.Consensus.HardFork.History.Qry Associated Types
| |||||
Generic SlotInEpoch | |||||
Defined in Ouroboros.Consensus.HardFork.History.Qry Associated Types
| |||||
Generic SlotInEra | |||||
Defined in Ouroboros.Consensus.HardFork.History.Qry Associated Types
| |||||
Generic TimeInEra | |||||
Defined in Ouroboros.Consensus.HardFork.History.Qry Associated Types
| |||||
Generic TimeInSlot | |||||
Defined in Ouroboros.Consensus.HardFork.History.Qry Associated Types
| |||||
Generic Bound | |||||
Defined in Ouroboros.Consensus.HardFork.History.Summary Associated Types
| |||||
Generic EraEnd | |||||
Defined in Ouroboros.Consensus.HardFork.History.Summary Associated Types
| |||||
Generic EraSummary | |||||
Defined in Ouroboros.Consensus.HardFork.History.Summary Associated Types
| |||||
Generic TriggerHardFork | |||||
Defined in Ouroboros.Consensus.HardFork.Simple Associated Types
Methods from :: TriggerHardFork -> Rep TriggerHardFork x # to :: Rep TriggerHardFork x -> TriggerHardFork # | |||||
Generic ComputeLedgerEvents | |||||
Defined in Ouroboros.Consensus.Ledger.Basics Associated Types
Methods from :: ComputeLedgerEvents -> Rep ComputeLedgerEvents x # to :: Rep ComputeLedgerEvents x -> ComputeLedgerEvents # | |||||
Generic CSJConfig | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic CSJEnabledConfig | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
Methods from :: CSJEnabledConfig -> Rep CSJEnabledConfig x # to :: Rep CSJEnabledConfig x -> CSJEnabledConfig # | |||||
Generic ChainSyncLoPBucketConfig | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
Methods from :: ChainSyncLoPBucketConfig -> Rep ChainSyncLoPBucketConfig x # to :: Rep ChainSyncLoPBucketConfig x -> ChainSyncLoPBucketConfig # | |||||
Generic ChainSyncLoPBucketEnabledConfig | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic DisengagedInitState | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: DisengagedInitState -> Rep DisengagedInitState x # to :: Rep DisengagedInitState x -> DisengagedInitState # | |||||
Generic JumperInitState | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: JumperInitState -> Rep JumperInitState x # to :: Rep JumperInitState x -> JumperInitState # | |||||
Generic ObjectorInitState | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ObjectorInitState -> Rep ObjectorInitState x # to :: Rep ObjectorInitState x -> ObjectorInitState # | |||||
Generic GsmState | |||||
Defined in Ouroboros.Consensus.Node.GsmState Associated Types
| |||||
Generic CoreNodeId | |||||
Defined in Ouroboros.Consensus.NodeId Associated Types
| |||||
Generic NodeId | |||||
Defined in Ouroboros.Consensus.NodeId Associated Types
| |||||
Generic BftParams | |||||
Defined in Ouroboros.Consensus.Protocol.BFT Associated Types
| |||||
Generic BftValidationErr | |||||
Defined in Ouroboros.Consensus.Protocol.BFT Associated Types
Methods from :: BftValidationErr -> Rep BftValidationErr x # to :: Rep BftValidationErr x -> BftValidationErr # | |||||
Generic LeaderSchedule | |||||
Defined in Ouroboros.Consensus.Protocol.LeaderSchedule Associated Types
Methods from :: LeaderSchedule -> Rep LeaderSchedule x # to :: Rep LeaderSchedule x -> LeaderSchedule # | |||||
Generic PBftParams | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
| |||||
Generic PBftSelectView | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftSelectView -> Rep PBftSelectView x # to :: Rep PBftSelectView x -> PBftSelectView # | |||||
Generic PBftSignatureThreshold | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftSignatureThreshold -> Rep PBftSignatureThreshold x # to :: Rep PBftSignatureThreshold x -> PBftSignatureThreshold # | |||||
Generic PBftMockVerKeyHash | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto Associated Types
Methods from :: PBftMockVerKeyHash -> Rep PBftMockVerKeyHash x # to :: Rep PBftMockVerKeyHash x -> PBftMockVerKeyHash # | |||||
Generic ChainType | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.API Associated Types
| |||||
Generic ScheduledGc | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Background Associated Types
| |||||
Generic BinaryBlockInfo | |||||
Defined in Ouroboros.Consensus.Storage.Common Associated Types
Methods from :: BinaryBlockInfo -> Rep BinaryBlockInfo x # to :: Rep BinaryBlockInfo x -> BinaryBlockInfo # | |||||
Generic PrefixLen | |||||
Defined in Ouroboros.Consensus.Storage.Common Associated Types
| |||||
Generic ChunkInfo | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal Associated Types
| |||||
Generic ChunkNo | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal Associated Types
| |||||
Generic ChunkSize | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal Associated Types
| |||||
Generic RelativeSlot | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal Associated Types
| |||||
Generic ChunkSlot | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Layout Associated Types
| |||||
Generic PrimaryIndex | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Primary Associated Types
| |||||
Generic BlockSize | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary Associated Types
| |||||
Generic BlockOrEBB | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
| |||||
Generic TraceCacheEvent | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
Methods from :: TraceCacheEvent -> Rep TraceCacheEvent x # to :: Rep TraceCacheEvent x -> TraceCacheEvent # | |||||
Generic ValidationPolicy | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
Methods from :: ValidationPolicy -> Rep ValidationPolicy x # to :: Rep ValidationPolicy x -> ValidationPolicy # | |||||
Generic NumOfDiskSnapshots | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy Associated Types
Methods from :: NumOfDiskSnapshots -> Rep NumOfDiskSnapshots x # to :: Rep NumOfDiskSnapshots x -> NumOfDiskSnapshots # | |||||
Generic SnapshotInterval | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy Associated Types
Methods from :: SnapshotInterval -> Rep SnapshotInterval x # to :: Rep SnapshotInterval x -> SnapshotInterval # | |||||
Generic DiskSnapshot | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Snapshots Associated Types
| |||||
Generic BlockOffset | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types Associated Types
| |||||
Generic BlockSize | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types Associated Types
| |||||
Generic BlocksPerFile | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types Associated Types
| |||||
Generic Fingerprint | |||||
Defined in Ouroboros.Consensus.Util.STM Associated Types
| |||||
Generic ByronPartialLedgerConfig | |||||
Defined in Ouroboros.Consensus.Byron.ByronHFC Associated Types
Methods from :: ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x # to :: Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig # | |||||
Generic ByronHash | |||||
Defined in Ouroboros.Consensus.Byron.Ledger.Block Associated Types
| |||||
Generic ByronOtherHeaderEnvelopeError | |||||
Defined in Ouroboros.Consensus.Byron.Ledger.HeaderValidation Associated Types
| |||||
Generic ByronTransition | |||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Associated Types
Methods from :: ByronTransition -> Rep ByronTransition x # to :: Rep ByronTransition x -> ByronTransition # | |||||
Generic CompactGenesis | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Config Associated Types
Methods from :: CompactGenesis -> Rep CompactGenesis x # to :: Rep CompactGenesis x -> CompactGenesis # | |||||
Generic ShelleyTransition | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger Associated Types
Methods from :: ShelleyTransition -> Rep ShelleyTransition x # to :: Rep ShelleyTransition x -> ShelleyTransition # | |||||
Generic AlonzoMeasure | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool Associated Types
| |||||
Generic ConwayMeasure | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool Associated Types
| |||||
Generic StakeSnapshot | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Associated Types
| |||||
Generic StakeSnapshots | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Associated Types
Methods from :: StakeSnapshots -> Rep StakeSnapshots x # to :: Rep StakeSnapshots x -> StakeSnapshots # | |||||
Generic ShelleyHash | |||||
Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract Associated Types
| |||||
Generic PraosEnvelopeError | |||||
Defined in Ouroboros.Consensus.Shelley.Protocol.Praos Associated Types
Methods from :: PraosEnvelopeError -> Rep PraosEnvelopeError x # to :: Rep PraosEnvelopeError x -> PraosEnvelopeError # | |||||
Generic GenesisConfig | |||||
Defined in Ouroboros.Consensus.Node.Genesis Associated Types
| |||||
Generic GenesisConfigFlags | |||||
Defined in Ouroboros.Consensus.Node.Genesis Associated Types
Methods from :: GenesisConfigFlags -> Rep GenesisConfigFlags x # to :: Rep GenesisConfigFlags x -> GenesisConfigFlags # | |||||
Generic LoEAndGDDParams | |||||
Defined in Ouroboros.Consensus.Node.Genesis Associated Types
| |||||
Generic KESInfo | |||||
Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey Associated Types
| |||||
Generic PraosParams | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
| |||||
Generic PraosState | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
| |||||
Generic MaxMajorProtVer | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Common Associated Types
Methods from :: MaxMajorProtVer -> Rep MaxMajorProtVer x # to :: Rep MaxMajorProtVer x -> MaxMajorProtVer # | |||||
Generic VRFTiebreakerFlavor | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Common Associated Types
Methods from :: VRFTiebreakerFlavor -> Rep VRFTiebreakerFlavor x # to :: Rep VRFTiebreakerFlavor x -> VRFTiebreakerFlavor # | |||||
Generic InputVRF | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.VRF Associated Types
| |||||
Generic TPraosParams | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
| |||||
Generic TPraosState | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
| |||||
Generic GenesisBlockFetchConfiguration | |||||
Defined in Ouroboros.Network.BlockFetch Associated Types
| |||||
Generic AverageMetrics | |||||
Defined in Ouroboros.Network.PeerSelection.PeerMetric Associated Types
| |||||
Generic PeerMetricsConfiguration | |||||
Defined in Ouroboros.Network.PeerSelection.PeerMetric Associated Types
Methods from :: PeerMetricsConfiguration -> Rep PeerMetricsConfiguration x # to :: Rep PeerMetricsConfiguration x -> PeerMetricsConfiguration # | |||||
Generic ConsensusMode | |||||
Defined in Cardano.Network.ConsensusMode Associated Types
| |||||
Generic UseBootstrapPeers | |||||
Defined in Cardano.Network.PeerSelection.Bootstrap Associated Types
Methods from :: UseBootstrapPeers -> Rep UseBootstrapPeers x # to :: Rep UseBootstrapPeers x -> UseBootstrapPeers # | |||||
Generic OutboundConnectionsState | |||||
Defined in Cardano.Network.PeerSelection.LocalRootPeers Associated Types
Methods from :: OutboundConnectionsState -> Rep OutboundConnectionsState x # to :: Rep OutboundConnectionsState x -> OutboundConnectionsState # | |||||
Generic PeerTrustable | |||||
Defined in Cardano.Network.PeerSelection.PeerTrustable Associated Types
| |||||
Generic LedgerStateJudgement | |||||
Defined in Cardano.Network.Types Associated Types
Methods from :: LedgerStateJudgement -> Rep LedgerStateJudgement x # to :: Rep LedgerStateJudgement x -> LedgerStateJudgement # | |||||
Generic MaxSlotNo | |||||
Defined in Ouroboros.Network.Block Associated Types
| |||||
Generic ChainSelStarvation | |||||
Defined in Ouroboros.Network.BlockFetch.ConsensusInterface Associated Types
Methods from :: ChainSelStarvation -> Rep ChainSelStarvation x # to :: Rep ChainSelStarvation x -> ChainSelStarvation # | |||||
Generic NetworkMagic | |||||
Defined in Ouroboros.Network.Magic Associated Types
| |||||
Generic NodeToClientVersion | |||||
Defined in Ouroboros.Network.NodeToClient.Version Associated Types
Methods from :: NodeToClientVersion -> Rep NodeToClientVersion x # to :: Rep NodeToClientVersion x -> NodeToClientVersion # | |||||
Generic NodeToNodeVersion | |||||
Defined in Ouroboros.Network.NodeToNode.Version Associated Types
Methods from :: NodeToNodeVersion -> Rep NodeToNodeVersion x # to :: Rep NodeToNodeVersion x -> NodeToNodeVersion # | |||||
Generic AfterSlot | |||||
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Associated Types
| |||||
Generic UseLedgerPeers | |||||
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Associated Types
Methods from :: UseLedgerPeers -> Rep UseLedgerPeers x # to :: Rep UseLedgerPeers x -> UseLedgerPeers # | |||||
Generic PeerAdvertise | |||||
Defined in Ouroboros.Network.PeerSelection.PeerAdvertise Associated Types
| |||||
Generic PeerSharing | |||||
Defined in Ouroboros.Network.PeerSelection.PeerSharing Associated Types
| |||||
Generic SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes Associated Types
| |||||
Generic FileDescriptor | |||||
Defined in Ouroboros.Network.Snocket Associated Types
Methods from :: FileDescriptor -> Rep FileDescriptor x # to :: Rep FileDescriptor x -> FileDescriptor # | |||||
Generic LocalAddress | |||||
Defined in Ouroboros.Network.Snocket Associated Types
| |||||
Generic LocalSocket | |||||
Defined in Ouroboros.Network.Snocket Associated Types
| |||||
Generic Cookie | |||||
Defined in Ouroboros.Network.Protocol.KeepAlive.Type Associated Types
| |||||
Generic AcquireFailure | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Associated Types
Methods from :: AcquireFailure -> Rep AcquireFailure x # to :: Rep AcquireFailure x -> AcquireFailure # | |||||
Generic MeasureName | |||||
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type Associated Types
| |||||
Generic MempoolMeasures | |||||
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type Associated Types
Methods from :: MempoolMeasures -> Rep MempoolMeasures x # to :: Rep MempoolMeasures x -> MempoolMeasures # | |||||
Generic MempoolSizeAndCapacity | |||||
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type Associated Types
Methods from :: MempoolSizeAndCapacity -> Rep MempoolSizeAndCapacity x # to :: Rep MempoolSizeAndCapacity x -> MempoolSizeAndCapacity # | |||||
Generic PeerSharingAmount | |||||
Defined in Ouroboros.Network.Protocol.PeerSharing.Type Associated Types
Methods from :: PeerSharingAmount -> Rep PeerSharingAmount x # to :: Rep PeerSharingAmount x -> PeerSharingAmount # | |||||
Generic NumTxIdsToAck | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Associated Types
| |||||
Generic NumTxIdsToReq | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Associated Types
| |||||
Generic Ann | |||||
Defined in PlutusCore.Annotation Associated Types
| |||||
Generic Inline | |||||
Defined in PlutusCore.Annotation Associated Types
| |||||
Generic SrcSpan | |||||
Defined in PlutusCore.Annotation Associated Types
| |||||
Generic SrcSpans | |||||
Defined in PlutusCore.Annotation Associated Types
| |||||
Generic Data | |||||
Defined in PlutusCore.Data Associated Types
| |||||
Generic DeBruijn | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
| |||||
Generic FreeVariableError | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
Methods from :: FreeVariableError -> Rep FreeVariableError x # to :: Rep FreeVariableError x -> FreeVariableError # | |||||
Generic Index | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
| |||||
Generic NamedDeBruijn | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
| |||||
Generic NamedTyDeBruijn | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
Methods from :: NamedTyDeBruijn -> Rep NamedTyDeBruijn x # to :: Rep NamedTyDeBruijn x -> NamedTyDeBruijn # | |||||
Generic TyDeBruijn | |||||
Defined in PlutusCore.DeBruijn.Internal Associated Types
| |||||
Generic DefaultFun | |||||
Defined in PlutusCore.Default.Builtins Associated Types
| |||||
Generic ParserError | |||||
Defined in PlutusCore.Error Associated Types
| |||||
Generic ParserErrorBundle | |||||
Defined in PlutusCore.Error Associated Types
Methods from :: ParserErrorBundle -> Rep ParserErrorBundle x # to :: Rep ParserErrorBundle x -> ParserErrorBundle # | |||||
Generic CkUserError | |||||
Defined in PlutusCore.Evaluation.Machine.Ck Associated Types
| |||||
Generic CostModelApplyError | |||||
Defined in PlutusCore.Evaluation.Machine.CostModelInterface Associated Types
Methods from :: CostModelApplyError -> Rep CostModelApplyError x # to :: Rep CostModelApplyError x -> CostModelApplyError # | |||||
Generic Coefficient0 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient00 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient01 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient02 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient1 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient10 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient11 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient2 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Coefficient20 | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Intercept | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic ModelConstantOrLinear | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelConstantOrLinear -> Rep ModelConstantOrLinear x # to :: Rep ModelConstantOrLinear x -> ModelConstantOrLinear # | |||||
Generic ModelConstantOrOneArgument | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelConstantOrOneArgument -> Rep ModelConstantOrOneArgument x # to :: Rep ModelConstantOrOneArgument x -> ModelConstantOrOneArgument # | |||||
Generic ModelConstantOrTwoArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelConstantOrTwoArguments -> Rep ModelConstantOrTwoArguments x # to :: Rep ModelConstantOrTwoArguments x -> ModelConstantOrTwoArguments # | |||||
Generic ModelFiveArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelFiveArguments -> Rep ModelFiveArguments x # to :: Rep ModelFiveArguments x -> ModelFiveArguments # | |||||
Generic ModelFourArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelFourArguments -> Rep ModelFourArguments x # to :: Rep ModelFourArguments x -> ModelFourArguments # | |||||
Generic ModelOneArgument | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelOneArgument -> Rep ModelOneArgument x # to :: Rep ModelOneArgument x -> ModelOneArgument # | |||||
Generic ModelSixArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelSixArguments -> Rep ModelSixArguments x # to :: Rep ModelSixArguments x -> ModelSixArguments # | |||||
Generic ModelSubtractedSizes | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelSubtractedSizes -> Rep ModelSubtractedSizes x # to :: Rep ModelSubtractedSizes x -> ModelSubtractedSizes # | |||||
Generic ModelThreeArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelThreeArguments -> Rep ModelThreeArguments x # to :: Rep ModelThreeArguments x -> ModelThreeArguments # | |||||
Generic ModelTwoArguments | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: ModelTwoArguments -> Rep ModelTwoArguments x # to :: Rep ModelTwoArguments x -> ModelTwoArguments # | |||||
Generic OneVariableLinearFunction | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: OneVariableLinearFunction -> Rep OneVariableLinearFunction x # to :: Rep OneVariableLinearFunction x -> OneVariableLinearFunction # | |||||
Generic OneVariableQuadraticFunction | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic Slope | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic TwoVariableLinearFunction | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: TwoVariableLinearFunction -> Rep TwoVariableLinearFunction x # to :: Rep TwoVariableLinearFunction x -> TwoVariableLinearFunction # | |||||
Generic TwoVariableQuadraticFunction | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
| |||||
Generic ExBudget | |||||
Defined in PlutusCore.Evaluation.Machine.ExBudget Associated Types
| |||||
Generic ExCPU | |||||
Defined in PlutusCore.Evaluation.Machine.ExMemory Associated Types
| |||||
Generic ExMemory | |||||
Defined in PlutusCore.Evaluation.Machine.ExMemory Associated Types
| |||||
Generic ExtensionFun | |||||
Defined in PlutusCore.Examples.Builtins Associated Types
| |||||
Generic Name | |||||
Defined in PlutusCore.Name.Unique Associated Types
| |||||
Generic TyName | |||||
Defined in PlutusCore.Name.Unique Associated Types
| |||||
Generic Version | |||||
Defined in PlutusCore.Version Associated Types
| |||||
Generic CekUserError | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal Associated Types
| |||||
Generic StepKind | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal Associated Types
| |||||
Generic DatatypeComponent | |||||
Defined in PlutusIR.Compiler.Provenance Associated Types
| |||||
Generic Recursivity | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic Strictness | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic SatInt | |||||
Defined in Data.SatInt Associated Types
| |||||
Generic EvaluationContext | |||||
Defined in PlutusLedgerApi.Common.Eval Associated Types
Methods from :: EvaluationContext -> Rep EvaluationContext x # to :: Rep EvaluationContext x -> EvaluationContext # | |||||
Generic MajorProtocolVersion | |||||
Defined in PlutusLedgerApi.Common.ProtocolVersions Associated Types
Methods from :: MajorProtocolVersion -> Rep MajorProtocolVersion x # to :: Rep MajorProtocolVersion x -> MajorProtocolVersion # | |||||
Generic ScriptForEvaluation | |||||
Defined in PlutusLedgerApi.Common.SerialisedScript Associated Types
Methods from :: ScriptForEvaluation -> Rep ScriptForEvaluation x # to :: Rep ScriptForEvaluation x -> ScriptForEvaluation # | |||||
Generic ScriptNamedDeBruijn | |||||
Defined in PlutusLedgerApi.Common.SerialisedScript Associated Types
Methods from :: ScriptNamedDeBruijn -> Rep ScriptNamedDeBruijn x # to :: Rep ScriptNamedDeBruijn x -> ScriptNamedDeBruijn # | |||||
Generic PlutusLedgerLanguage | |||||
Defined in PlutusLedgerApi.Common.Versions Associated Types
Methods from :: PlutusLedgerLanguage -> Rep PlutusLedgerLanguage x # to :: Rep PlutusLedgerLanguage x -> PlutusLedgerLanguage # | |||||
Generic Address | |||||
Defined in PlutusLedgerApi.V1.Address Associated Types
| |||||
Generic LedgerBytes | |||||
Defined in PlutusLedgerApi.V1.Bytes Associated Types
| |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V1.Contexts Associated Types
| |||||
Generic ScriptPurpose | |||||
Defined in PlutusLedgerApi.V1.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V1.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V1.Contexts Associated Types
| |||||
Generic Credential | |||||
Defined in PlutusLedgerApi.V1.Credential Associated Types
| |||||
Generic StakingCredential | |||||
Defined in PlutusLedgerApi.V1.Credential Associated Types
Methods from :: StakingCredential -> Rep StakingCredential x # to :: Rep StakingCredential x -> StakingCredential # | |||||
Generic PubKeyHash | |||||
Defined in PlutusLedgerApi.V1.Crypto Associated Types
| |||||
Generic DCert | |||||
Defined in PlutusLedgerApi.V1.DCert Associated Types
| |||||
Generic Address | |||||
Defined in PlutusLedgerApi.V1.Data.Address Associated Types
| |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V1.Data.Contexts Associated Types
| |||||
Generic ScriptPurpose | |||||
Defined in PlutusLedgerApi.V1.Data.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V1.Data.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V1.Data.Contexts Associated Types
| |||||
Generic Credential | |||||
Defined in PlutusLedgerApi.V1.Data.Credential Associated Types
| |||||
Generic StakingCredential | |||||
Defined in PlutusLedgerApi.V1.Data.Credential Associated Types
Methods from :: StakingCredential -> Rep StakingCredential x # to :: Rep StakingCredential x -> StakingCredential # | |||||
Generic DCert | |||||
Defined in PlutusLedgerApi.V1.Data.DCert Associated Types
| |||||
Generic DiffMilliSeconds | |||||
Defined in PlutusLedgerApi.V1.Data.Time Associated Types
Methods from :: DiffMilliSeconds -> Rep DiffMilliSeconds x # to :: Rep DiffMilliSeconds x -> DiffMilliSeconds # | |||||
Generic POSIXTime | |||||
Defined in PlutusLedgerApi.V1.Data.Time Associated Types
| |||||
Generic RedeemerPtr | |||||
Defined in PlutusLedgerApi.V1.Data.Tx Associated Types
| |||||
Generic ScriptTag | |||||
Defined in PlutusLedgerApi.V1.Data.Tx Associated Types
| |||||
Generic TxId | |||||
Defined in PlutusLedgerApi.V1.Data.Tx Associated Types
| |||||
Generic TxOut | |||||
Defined in PlutusLedgerApi.V1.Data.Tx Associated Types
| |||||
Generic TxOutRef | |||||
Defined in PlutusLedgerApi.V1.Data.Tx Associated Types
| |||||
Generic AssetClass | |||||
Defined in PlutusLedgerApi.V1.Data.Value Associated Types
| |||||
Generic CurrencySymbol | |||||
Defined in PlutusLedgerApi.V1.Data.Value Associated Types
Methods from :: CurrencySymbol -> Rep CurrencySymbol x # to :: Rep CurrencySymbol x -> CurrencySymbol # | |||||
Generic Lovelace | |||||
Defined in PlutusLedgerApi.V1.Data.Value Associated Types
| |||||
Generic TokenName | |||||
Defined in PlutusLedgerApi.V1.Data.Value Associated Types
| |||||
Generic Value | |||||
Defined in PlutusLedgerApi.V1.Data.Value Associated Types
| |||||
Generic ParamName | |||||
Defined in PlutusLedgerApi.V1.ParamName Associated Types
| |||||
Generic Datum | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic DatumHash | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic Redeemer | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic RedeemerHash | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic ScriptError | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic ScriptHash | |||||
Defined in PlutusLedgerApi.V1.Scripts Associated Types
| |||||
Generic DiffMilliSeconds | |||||
Defined in PlutusLedgerApi.V1.Time Associated Types
Methods from :: DiffMilliSeconds -> Rep DiffMilliSeconds x # to :: Rep DiffMilliSeconds x -> DiffMilliSeconds # | |||||
Generic POSIXTime | |||||
Defined in PlutusLedgerApi.V1.Time Associated Types
| |||||
Generic RedeemerPtr | |||||
Defined in PlutusLedgerApi.V1.Tx Associated Types
| |||||
Generic ScriptTag | |||||
Defined in PlutusLedgerApi.V1.Tx Associated Types
| |||||
Generic TxId | |||||
Defined in PlutusLedgerApi.V1.Tx Associated Types
| |||||
Generic TxOut | |||||
Defined in PlutusLedgerApi.V1.Tx Associated Types
| |||||
Generic TxOutRef | |||||
Defined in PlutusLedgerApi.V1.Tx Associated Types
| |||||
Generic AssetClass | |||||
Defined in PlutusLedgerApi.V1.Value Associated Types
| |||||
Generic CurrencySymbol | |||||
Defined in PlutusLedgerApi.V1.Value Associated Types
Methods from :: CurrencySymbol -> Rep CurrencySymbol x # to :: Rep CurrencySymbol x -> CurrencySymbol # | |||||
Generic Lovelace | |||||
Defined in PlutusLedgerApi.V1.Value Associated Types
| |||||
Generic TokenName | |||||
Defined in PlutusLedgerApi.V1.Value Associated Types
| |||||
Generic Value | |||||
Defined in PlutusLedgerApi.V1.Value Associated Types
| |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V2.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V2.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V2.Contexts Associated Types
| |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V2.Data.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V2.Data.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V2.Data.Contexts Associated Types
| |||||
Generic OutputDatum | |||||
Defined in PlutusLedgerApi.V2.Data.Tx Associated Types
| |||||
Generic TxOut | |||||
Defined in PlutusLedgerApi.V2.Data.Tx Associated Types
| |||||
Generic ParamName | |||||
Defined in PlutusLedgerApi.V2.ParamName Associated Types
| |||||
Generic OutputDatum | |||||
Defined in PlutusLedgerApi.V2.Tx Associated Types
| |||||
Generic TxOut | |||||
Defined in PlutusLedgerApi.V2.Tx Associated Types
| |||||
Generic ChangedParameters | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: ChangedParameters -> Rep ChangedParameters x # to :: Rep ChangedParameters x -> ChangedParameters # | |||||
Generic ColdCommitteeCredential | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: ColdCommitteeCredential -> Rep ColdCommitteeCredential x # to :: Rep ColdCommitteeCredential x -> ColdCommitteeCredential # | |||||
Generic Committee | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic Constitution | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic DRep | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic DRepCredential | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: DRepCredential -> Rep DRepCredential x # to :: Rep DRepCredential x -> DRepCredential # | |||||
Generic Delegatee | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic GovernanceAction | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: GovernanceAction -> Rep GovernanceAction x # to :: Rep GovernanceAction x -> GovernanceAction # | |||||
Generic GovernanceActionId | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: GovernanceActionId -> Rep GovernanceActionId x # to :: Rep GovernanceActionId x -> GovernanceActionId # | |||||
Generic HotCommitteeCredential | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: HotCommitteeCredential -> Rep HotCommitteeCredential x # to :: Rep HotCommitteeCredential x -> HotCommitteeCredential # | |||||
Generic ProposalProcedure | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: ProposalProcedure -> Rep ProposalProcedure x # to :: Rep ProposalProcedure x -> ProposalProcedure # | |||||
Generic ProtocolVersion | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
Methods from :: ProtocolVersion -> Rep ProtocolVersion x # to :: Rep ProtocolVersion x -> ProtocolVersion # | |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic ScriptInfo | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic ScriptPurpose | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic TxCert | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic Vote | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic Voter | |||||
Defined in PlutusLedgerApi.V3.Contexts Associated Types
| |||||
Generic ChangedParameters | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: ChangedParameters -> Rep ChangedParameters x # to :: Rep ChangedParameters x -> ChangedParameters # | |||||
Generic ColdCommitteeCredential | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: ColdCommitteeCredential -> Rep ColdCommitteeCredential x # to :: Rep ColdCommitteeCredential x -> ColdCommitteeCredential # | |||||
Generic Committee | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic Constitution | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic DRep | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic DRepCredential | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: DRepCredential -> Rep DRepCredential x # to :: Rep DRepCredential x -> DRepCredential # | |||||
Generic Delegatee | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic GovernanceAction | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: GovernanceAction -> Rep GovernanceAction x # to :: Rep GovernanceAction x -> GovernanceAction # | |||||
Generic GovernanceActionId | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: GovernanceActionId -> Rep GovernanceActionId x # to :: Rep GovernanceActionId x -> GovernanceActionId # | |||||
Generic HotCommitteeCredential | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: HotCommitteeCredential -> Rep HotCommitteeCredential x # to :: Rep HotCommitteeCredential x -> HotCommitteeCredential # | |||||
Generic ProposalProcedure | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: ProposalProcedure -> Rep ProposalProcedure x # to :: Rep ProposalProcedure x -> ProposalProcedure # | |||||
Generic ProtocolVersion | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
Methods from :: ProtocolVersion -> Rep ProtocolVersion x # to :: Rep ProtocolVersion x -> ProtocolVersion # | |||||
Generic ScriptContext | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic ScriptInfo | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic ScriptPurpose | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic TxCert | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic TxInInfo | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic TxInfo | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic Vote | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic Voter | |||||
Defined in PlutusLedgerApi.V3.Data.Contexts Associated Types
| |||||
Generic MintValue | |||||
Defined in PlutusLedgerApi.V3.Data.MintValue Associated Types
| |||||
Generic TxId | |||||
Defined in PlutusLedgerApi.V3.Data.Tx Associated Types
| |||||
Generic TxOutRef | |||||
Defined in PlutusLedgerApi.V3.Data.Tx Associated Types
| |||||
Generic MintValue | |||||
Defined in PlutusLedgerApi.V3.MintValue Associated Types
| |||||
Generic ParamName | |||||
Defined in PlutusLedgerApi.V3.ParamName Associated Types
| |||||
Generic TxId | |||||
Defined in PlutusLedgerApi.V3.Tx Associated Types
| |||||
Generic TxOutRef | |||||
Defined in PlutusLedgerApi.V3.Tx Associated Types
| |||||
Generic DefinitionId | |||||
Defined in PlutusTx.Blueprint.Definition.Id Associated Types
| |||||
Generic Preamble | |||||
Defined in PlutusTx.Blueprint.Preamble Associated Types
| |||||
Generic BytesSchema | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
| |||||
Generic IntegerSchema | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
| |||||
Generic SchemaAnn | |||||
Defined in PlutusTx.Blueprint.Schema.Annotation Associated Types
| |||||
Generic SchemaInfo | |||||
Defined in PlutusTx.Blueprint.Schema.Annotation Associated Types
| |||||
Generic BuiltinData | |||||
Defined in PlutusTx.Builtins.Internal Associated Types
| |||||
Generic CovLoc | |||||
Defined in PlutusTx.Coverage Associated Types
| |||||
Generic CoverageAnnotation | |||||
Defined in PlutusTx.Coverage Associated Types
Methods from :: CoverageAnnotation -> Rep CoverageAnnotation x # to :: Rep CoverageAnnotation x -> CoverageAnnotation # | |||||
Generic CoverageData | |||||
Defined in PlutusTx.Coverage Associated Types
| |||||
Generic CoverageIndex | |||||
Defined in PlutusTx.Coverage Associated Types
| |||||
Generic CoverageMetadata | |||||
Defined in PlutusTx.Coverage Associated Types
Methods from :: CoverageMetadata -> Rep CoverageMetadata x # to :: Rep CoverageMetadata x -> CoverageMetadata # | |||||
Generic CoverageReport | |||||
Defined in PlutusTx.Coverage Associated Types
Methods from :: CoverageReport -> Rep CoverageReport x # to :: Rep CoverageReport x -> CoverageReport # | |||||
Generic Metadata | |||||
Defined in PlutusTx.Coverage Associated Types
| |||||
Generic Rational | |||||
Defined in PlutusTx.Ratio Associated Types
| |||||
Generic ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal Associated Types
| |||||
Generic Mode | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic Style | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic TextDetails | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic Doc | |||||
Defined in Text.PrettyPrint.HughesPJ Associated Types
| |||||
Generic ColorOptions | |||||
Defined in Text.Pretty.Simple.Internal.Color Associated Types
| |||||
Generic Style | |||||
Defined in Text.Pretty.Simple.Internal.Color Associated Types
| |||||
Generic Expr | |||||
Defined in Text.Pretty.Simple.Internal.Expr Associated Types
| |||||
Generic CheckColorTty | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
Generic OutputOptions | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
| |||||
Generic StringOutputStyle | |||||
Defined in Text.Pretty.Simple.Internal.Printer Associated Types
Methods from :: StringOutputStyle -> Rep StringOutputStyle x # to :: Rep StringOutputStyle x -> StringOutputStyle # | |||||
Generic RAWState | |||||
Defined in Control.RAWLock Associated Types
| |||||
Generic RegistryStatus | |||||
Defined in Control.ResourceRegistry Associated Types
| |||||
Generic RetryAction | |||||
Defined in Control.Retry Associated Types
| |||||
Generic RetryStatus | |||||
Defined in Control.Retry Associated Types
| |||||
Generic Approximation | |||||
Defined in Money.Internal Associated Types
| |||||
Generic Scale | |||||
Defined in Money.Internal Associated Types
| |||||
Generic SomeDense | |||||
Defined in Money.Internal Associated Types
| |||||
Generic SomeDiscrete | |||||
Defined in Money.Internal Associated Types
| |||||
Generic SomeExchangeRate | |||||
Defined in Money.Internal Associated Types
Methods from :: SomeExchangeRate -> Rep SomeExchangeRate x # to :: Rep SomeExchangeRate x -> SomeExchangeRate # | |||||
Generic AcceptHeader | |||||
Defined in Servant.API.ContentTypes Associated Types
| |||||
Generic NoContent | |||||
Defined in Servant.API.ContentTypes | |||||
Generic IsSecure | |||||
Defined in Servant.API.IsSecure Associated Types
| |||||
Generic BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl Associated Types
| |||||
Generic Scheme | |||||
Defined in Servant.Client.Core.BaseUrl Associated Types
| |||||
Generic ClientError | |||||
Defined in Servant.Client.Core.ClientError Associated Types
| |||||
Generic RequestBody | |||||
Defined in Servant.Client.Core.Request Associated Types
| |||||
Generic Endpoint | |||||
Defined in Servant.Docs.Internal Associated Types
| |||||
Generic Time | |||||
Defined in Control.Monad.Class.MonadTime.SI Associated Types
| |||||
Generic StudentT | |||||
Defined in Statistics.Distribution.StudentT Associated Types
| |||||
Generic ApiKeyLocation | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: ApiKeyLocation -> Rep ApiKeyLocation x # to :: Rep ApiKeyLocation x -> ApiKeyLocation # | |||||
Generic ApiKeyParams | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Contact | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Example | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic ExternalDocs | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Header | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Host | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Info | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic License | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic NamedSchema | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic OAuth2Flow | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic OAuth2Params | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Operation | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Param | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic ParamAnySchema | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: ParamAnySchema -> Rep ParamAnySchema x # to :: Rep ParamAnySchema x -> ParamAnySchema # | |||||
Generic ParamLocation | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic ParamOtherSchema | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: ParamOtherSchema -> Rep ParamOtherSchema x # to :: Rep ParamOtherSchema x -> ParamOtherSchema # | |||||
Generic PathItem | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Response | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Responses | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Schema | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Scheme | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic SecurityDefinitions | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: SecurityDefinitions -> Rep SecurityDefinitions x # to :: Rep SecurityDefinitions x -> SecurityDefinitions # | |||||
Generic SecurityScheme | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: SecurityScheme -> Rep SecurityScheme x # to :: Rep SecurityScheme x -> SecurityScheme # | |||||
Generic SecuritySchemeType | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: SecuritySchemeType -> Rep SecuritySchemeType x # to :: Rep SecuritySchemeType x -> SecuritySchemeType # | |||||
Generic Swagger | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Tag | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Xml | |||||
Defined in Data.Swagger.Internal Associated Types
| |||||
Generic Outcome | |||||
Defined in Test.Tasty.Core Associated Types
| |||||
Generic Expr | |||||
Defined in Test.Tasty.Patterns.Types Associated Types
| |||||
Generic AnnLookup | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic AnnTarget | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Bang | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic BndrVis | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Body | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Bytes | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Callconv | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Clause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Con | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Dec | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DecidedStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic DerivClause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DerivStrategy | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic DocLoc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Exp | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FamilyResultSig | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FamilyResultSig -> Rep FamilyResultSig x # to :: Rep FamilyResultSig x -> FamilyResultSig # | |||||
Generic Fixity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FixityDirection | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FixityDirection -> Rep FixityDirection x # to :: Rep FixityDirection x -> FixityDirection # | |||||
Generic Foreign | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic FunDep | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Guard | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Info | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic InjectivityAnn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: InjectivityAnn -> Rep InjectivityAnn x # to :: Rep InjectivityAnn x -> InjectivityAnn # | |||||
Generic Inline | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Lit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Loc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Match | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic ModName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Module | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic ModuleInfo | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Name | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NameFlavour | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NameSpace | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic NamespaceSpecifier | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: NamespaceSpecifier -> Rep NamespaceSpecifier x # to :: Rep NamespaceSpecifier x -> NamespaceSpecifier # | |||||
Generic OccName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Overlap | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Pat | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PatSynArgs | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PatSynDir | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Phases | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic PkgName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Pragma | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Range | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Role | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic RuleBndr | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic RuleMatch | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Safety | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic SourceStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic Specificity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Stmt | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TyLit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TySynEqn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic Type | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic TypeFamilyHead | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: TypeFamilyHead -> Rep TypeFamilyHead x # to :: Rep TypeFamilyHead x -> TypeFamilyHead # | |||||
Generic ConstructorInfo | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorInfo -> Rep ConstructorInfo x # to :: Rep ConstructorInfo x -> ConstructorInfo # | |||||
Generic ConstructorVariant | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorVariant -> Rep ConstructorVariant x # to :: Rep ConstructorVariant x -> ConstructorVariant # | |||||
Generic DatatypeInfo | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
Generic DatatypeVariant | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: DatatypeVariant -> Rep DatatypeVariant x # to :: Rep DatatypeVariant x -> DatatypeVariant # | |||||
Generic FieldStrictness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: FieldStrictness -> Rep FieldStrictness x # to :: Rep FieldStrictness x -> FieldStrictness # | |||||
Generic Strictness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
Generic Unpackedness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
Generic Group | |||||
Defined in Network.TLS.Crypto.Types Associated Types
| |||||
Generic CipherId | |||||
Defined in Network.TLS.Types.Cipher Associated Types
| |||||
Generic SessionData | |||||
Defined in Network.TLS.Types.Session Associated Types
| |||||
Generic SessionFlag | |||||
Defined in Network.TLS.Types.Session Associated Types
| |||||
Generic TLS13TicketInfo | |||||
Defined in Network.TLS.Types.Session Associated Types
Methods from :: TLS13TicketInfo -> Rep TLS13TicketInfo x # to :: Rep TLS13TicketInfo x -> TLS13TicketInfo # | |||||
Generic Version | |||||
Defined in Network.TLS.Types.Version Associated Types
| |||||
Generic BackendConfig | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic ConfigOption | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic DetailLevel | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic ForwarderMode | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic LoggingContext | |||||
Defined in Cardano.Logging.Types Associated Types
Methods from :: LoggingContext -> Rep LoggingContext x # to :: Rep LoggingContext x -> LoggingContext # | |||||
Generic Privacy | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic SeverityS | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic TraceObject | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic TraceOptionForwarder | |||||
Defined in Cardano.Logging.Types Associated Types
Methods from :: TraceOptionForwarder -> Rep TraceOptionForwarder x # to :: Rep TraceOptionForwarder x -> TraceOptionForwarder # | |||||
Generic Verbosity | |||||
Defined in Cardano.Logging.Types Associated Types
| |||||
Generic NumberOfTraceObjects | |||||
Defined in Trace.Forward.Protocol.TraceObject.Type Associated Types
Methods from :: NumberOfTraceObjects -> Rep NumberOfTraceObjects x # to :: Rep NumberOfTraceObjects x -> NumberOfTraceObjects # | |||||
Generic UnixTime | |||||
Defined in Data.UnixTime.Types Associated Types
| |||||
Generic ConcException | |||||
Defined in UnliftIO.Internals.Async Associated Types
| |||||
Generic CompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: CompressParams -> Rep CompressParams x # to :: Rep CompressParams x -> CompressParams # | |||||
Generic DecompressError | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressError -> Rep DecompressError x # to :: Rep DecompressError x -> DecompressError # | |||||
Generic DecompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressParams -> Rep DecompressParams x # to :: Rep DecompressParams x -> DecompressParams # | |||||
Generic CompressionLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionLevel -> Rep CompressionLevel x # to :: Rep CompressionLevel x -> CompressionLevel # | |||||
Generic CompressionStrategy | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionStrategy -> Rep CompressionStrategy x # to :: Rep CompressionStrategy x -> CompressionStrategy # | |||||
Generic Format | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic MemoryLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic Method | |||||
Defined in Codec.Compression.Zlib.Stream | |||||
Generic WindowBits | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
Generic () | |||||
Generic Bool | |||||
Defined in GHC.Internal.Generics | |||||
Generic (Last' a) | |||||
Defined in Distribution.Compat.Semigroup Associated Types
| |||||
Generic (Option' a) | |||||
Defined in Distribution.Compat.Semigroup Associated Types
| |||||
Generic (Only a) | |||||
Defined in Data.Tuple.Only Associated Types
| |||||
Generic (Graph a) | |||||
Defined in Algebra.Graph Associated Types
| |||||
Generic (AdjacencyMap a) | |||||
Defined in Algebra.Graph.AdjacencyMap Associated Types
Methods from :: AdjacencyMap a -> Rep (AdjacencyMap a) x # to :: Rep (AdjacencyMap a) x -> AdjacencyMap a # | |||||
Generic (AdjacencyMap a) | |||||
Defined in Algebra.Graph.NonEmpty.AdjacencyMap Associated Types
Methods from :: AdjacencyMap a -> Rep (AdjacencyMap a) x # to :: Rep (AdjacencyMap a) x -> AdjacencyMap a # | |||||
Generic (Graph a) | |||||
Defined in Algebra.Graph.Undirected Associated Types
| |||||
Generic (SelectionParams f) # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: SelectionParams f -> Rep (SelectionParams f) x # to :: Rep (SelectionParams f) x -> SelectionParams f # | |||||
Generic (SelectionResult f) # | |||||
Defined in GeniusYield.Transaction.CoinSelection.Balance Associated Types
Methods from :: SelectionResult f -> Rep (SelectionResult f) x # to :: Rep (SelectionResult f) x -> SelectionResult f # | |||||
Generic (UTxOIndex u) # | |||||
Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal Associated Types
| |||||
Generic (UTxOSelection u) # | |||||
Defined in GeniusYield.Transaction.CoinSelection.UTxOSelection Associated Types
Methods from :: UTxOSelection u -> Rep (UTxOSelection u) x # to :: Rep (UTxOSelection u) x -> UTxOSelection u # | |||||
Generic (UTxOSelectionNonEmpty u) # | |||||
Defined in GeniusYield.Transaction.CoinSelection.UTxOSelection Associated Types
Methods from :: UTxOSelectionNonEmpty u -> Rep (UTxOSelectionNonEmpty u) x # to :: Rep (UTxOSelectionNonEmpty u) x -> UTxOSelectionNonEmpty u # | |||||
Generic (Complex a) | |||||
Defined in Data.Complex Associated Types
| |||||
Generic (First a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Last a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Max a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (Min a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (WrappedMonoid m) | |||||
Defined in Data.Semigroup Associated Types
Methods from :: WrappedMonoid m -> Rep (WrappedMonoid m) x # to :: Rep (WrappedMonoid m) x -> WrappedMonoid m # | |||||
Generic (BlockfrostAPI route) | |||||
Defined in Blockfrost.API Associated Types
Methods from :: BlockfrostAPI route -> Rep (BlockfrostAPI route) x # to :: Rep (BlockfrostAPI route) x -> BlockfrostAPI route # | |||||
Generic (BlockfrostV0API route) | |||||
Defined in Blockfrost.API Associated Types
Methods from :: BlockfrostV0API route -> Rep (BlockfrostV0API route) x # to :: Rep (BlockfrostV0API route) x -> BlockfrostV0API route # | |||||
Generic (CardanoAPI route) | |||||
Defined in Blockfrost.API Associated Types
Methods from :: CardanoAPI route -> Rep (CardanoAPI route) x # to :: Rep (CardanoAPI route) x -> CardanoAPI route # | |||||
Generic (AccountsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Accounts Associated Types
Methods from :: AccountsAPI route -> Rep (AccountsAPI route) x # to :: Rep (AccountsAPI route) x -> AccountsAPI route # | |||||
Generic (AddressesAPI route) | |||||
Defined in Blockfrost.API.Cardano.Addresses Associated Types
Methods from :: AddressesAPI route -> Rep (AddressesAPI route) x # to :: Rep (AddressesAPI route) x -> AddressesAPI route # | |||||
Generic (AssetsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Assets Associated Types
| |||||
Generic (BlocksAPI route) | |||||
Defined in Blockfrost.API.Cardano.Blocks Associated Types
| |||||
Generic (EpochsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Epochs Associated Types
| |||||
Generic (LedgerAPI route) | |||||
Defined in Blockfrost.API.Cardano.Ledger Associated Types
| |||||
Generic (MempoolAPI route) | |||||
Defined in Blockfrost.API.Cardano.Mempool Associated Types
Methods from :: MempoolAPI route -> Rep (MempoolAPI route) x # to :: Rep (MempoolAPI route) x -> MempoolAPI route # | |||||
Generic (MetadataAPI route) | |||||
Defined in Blockfrost.API.Cardano.Metadata Associated Types
Methods from :: MetadataAPI route -> Rep (MetadataAPI route) x # to :: Rep (MetadataAPI route) x -> MetadataAPI route # | |||||
Generic (NetworkAPI route) | |||||
Defined in Blockfrost.API.Cardano.Network Associated Types
Methods from :: NetworkAPI route -> Rep (NetworkAPI route) x # to :: Rep (NetworkAPI route) x -> NetworkAPI route # | |||||
Generic (PoolsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Pools Associated Types
| |||||
Generic (ScriptsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Scripts Associated Types
Methods from :: ScriptsAPI route -> Rep (ScriptsAPI route) x # to :: Rep (ScriptsAPI route) x -> ScriptsAPI route # | |||||
Generic (TransactionsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Transactions Associated Types
Methods from :: TransactionsAPI route -> Rep (TransactionsAPI route) x # to :: Rep (TransactionsAPI route) x -> TransactionsAPI route # | |||||
Generic (UtilsAPI route) | |||||
Defined in Blockfrost.API.Cardano.Utils Associated Types
| |||||
Generic (CommonAPI route) | |||||
Defined in Blockfrost.API.Common Associated Types
| |||||
Generic (IPFSAPI route) | |||||
Defined in Blockfrost.API.IPFS Associated Types
| |||||
Generic (NutLinkAPI route) | |||||
Defined in Blockfrost.API.NutLink Associated Types
Methods from :: NutLinkAPI route -> Rep (NutLinkAPI route) x # to :: Rep (NutLinkAPI route) x -> NutLinkAPI route # | |||||
Generic (Script elem) | |||||
Defined in Cardano.Address.Script Associated Types
| |||||
Generic (VotingProcedures era) | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods from :: VotingProcedures era -> Rep (VotingProcedures era) x # to :: Rep (VotingProcedures era) x -> VotingProcedures era # | |||||
Generic (Authors CIP108) | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic (Body CIP119) | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic (Body CIP108) | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic (HashAlgorithm CIP119) | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
Methods from :: HashAlgorithm CIP119 -> Rep (HashAlgorithm CIP119) x # to :: Rep (HashAlgorithm CIP119) x -> HashAlgorithm CIP119 # | |||||
Generic (HashAlgorithm CIP108) | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
Methods from :: HashAlgorithm CIP108 -> Rep (HashAlgorithm CIP108) x # to :: Rep (HashAlgorithm CIP108) x -> HashAlgorithm CIP108 # | |||||
Generic (TxValidationError era) | |||||
Defined in Cardano.Api.Internal.InMode Associated Types
| |||||
Generic (SigDSIGN Ed25519Bip32DSIGN) | |||||
Defined in Cardano.Api.Crypto.Ed25519Bip32 Associated Types
Methods from :: SigDSIGN Ed25519Bip32DSIGN -> Rep (SigDSIGN Ed25519Bip32DSIGN) x # to :: Rep (SigDSIGN Ed25519Bip32DSIGN) x -> SigDSIGN Ed25519Bip32DSIGN # | |||||
Generic (SigDSIGN EcdsaSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Associated Types
Methods from :: SigDSIGN EcdsaSecp256k1DSIGN -> Rep (SigDSIGN EcdsaSecp256k1DSIGN) x # to :: Rep (SigDSIGN EcdsaSecp256k1DSIGN) x -> SigDSIGN EcdsaSecp256k1DSIGN # | |||||
Generic (SigDSIGN Ed25519DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed25519 Associated Types
Methods from :: SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x # to :: Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN # | |||||
Generic (SigDSIGN Ed448DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed448 Associated Types
Methods from :: SigDSIGN Ed448DSIGN -> Rep (SigDSIGN Ed448DSIGN) x # to :: Rep (SigDSIGN Ed448DSIGN) x -> SigDSIGN Ed448DSIGN # | |||||
Generic (SigDSIGN MockDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Mock Associated Types
| |||||
Generic (SigDSIGN NeverDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.NeverUsed Associated Types
Methods from :: SigDSIGN NeverDSIGN -> Rep (SigDSIGN NeverDSIGN) x # to :: Rep (SigDSIGN NeverDSIGN) x -> SigDSIGN NeverDSIGN # | |||||
Generic (SigDSIGN SchnorrSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Associated Types
Methods from :: SigDSIGN SchnorrSecp256k1DSIGN -> Rep (SigDSIGN SchnorrSecp256k1DSIGN) x # to :: Rep (SigDSIGN SchnorrSecp256k1DSIGN) x -> SigDSIGN SchnorrSecp256k1DSIGN # | |||||
Generic (SigDSIGN ByronDSIGN) | |||||
Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN Associated Types
Methods from :: SigDSIGN ByronDSIGN -> Rep (SigDSIGN ByronDSIGN) x # to :: Rep (SigDSIGN ByronDSIGN) x -> SigDSIGN ByronDSIGN # | |||||
Generic (SignKeyDSIGN Ed25519Bip32DSIGN) | |||||
Defined in Cardano.Api.Crypto.Ed25519Bip32 Associated Types
Methods from :: SignKeyDSIGN Ed25519Bip32DSIGN -> Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x # to :: Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x -> SignKeyDSIGN Ed25519Bip32DSIGN # | |||||
Generic (SignKeyDSIGN EcdsaSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Associated Types
Methods from :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x # to :: Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x -> SignKeyDSIGN EcdsaSecp256k1DSIGN # | |||||
Generic (SignKeyDSIGN Ed25519DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed25519 Associated Types
Methods from :: SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x # to :: Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN # | |||||
Generic (SignKeyDSIGN Ed448DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed448 Associated Types
Methods from :: SignKeyDSIGN Ed448DSIGN -> Rep (SignKeyDSIGN Ed448DSIGN) x # to :: Rep (SignKeyDSIGN Ed448DSIGN) x -> SignKeyDSIGN Ed448DSIGN # | |||||
Generic (SignKeyDSIGN MockDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Mock Associated Types
Methods from :: SignKeyDSIGN MockDSIGN -> Rep (SignKeyDSIGN MockDSIGN) x # to :: Rep (SignKeyDSIGN MockDSIGN) x -> SignKeyDSIGN MockDSIGN # | |||||
Generic (SignKeyDSIGN NeverDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.NeverUsed Associated Types
Methods from :: SignKeyDSIGN NeverDSIGN -> Rep (SignKeyDSIGN NeverDSIGN) x # to :: Rep (SignKeyDSIGN NeverDSIGN) x -> SignKeyDSIGN NeverDSIGN # | |||||
Generic (SignKeyDSIGN SchnorrSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Associated Types
Methods from :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x # to :: Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x -> SignKeyDSIGN SchnorrSecp256k1DSIGN # | |||||
Generic (SignKeyDSIGN ByronDSIGN) | |||||
Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN Associated Types
Methods from :: SignKeyDSIGN ByronDSIGN -> Rep (SignKeyDSIGN ByronDSIGN) x # to :: Rep (SignKeyDSIGN ByronDSIGN) x -> SignKeyDSIGN ByronDSIGN # | |||||
Generic (VerKeyDSIGN Ed25519Bip32DSIGN) | |||||
Defined in Cardano.Api.Crypto.Ed25519Bip32 Associated Types
Methods from :: VerKeyDSIGN Ed25519Bip32DSIGN -> Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x # to :: Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x -> VerKeyDSIGN Ed25519Bip32DSIGN # | |||||
Generic (VerKeyDSIGN EcdsaSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Associated Types
Methods from :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x # to :: Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x -> VerKeyDSIGN EcdsaSecp256k1DSIGN # | |||||
Generic (VerKeyDSIGN Ed25519DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed25519 Associated Types
Methods from :: VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x # to :: Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN # | |||||
Generic (VerKeyDSIGN Ed448DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Ed448 Associated Types
Methods from :: VerKeyDSIGN Ed448DSIGN -> Rep (VerKeyDSIGN Ed448DSIGN) x # to :: Rep (VerKeyDSIGN Ed448DSIGN) x -> VerKeyDSIGN Ed448DSIGN # | |||||
Generic (VerKeyDSIGN MockDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.Mock Associated Types
Methods from :: VerKeyDSIGN MockDSIGN -> Rep (VerKeyDSIGN MockDSIGN) x # to :: Rep (VerKeyDSIGN MockDSIGN) x -> VerKeyDSIGN MockDSIGN # | |||||
Generic (VerKeyDSIGN NeverDSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.NeverUsed Associated Types
Methods from :: VerKeyDSIGN NeverDSIGN -> Rep (VerKeyDSIGN NeverDSIGN) x # to :: Rep (VerKeyDSIGN NeverDSIGN) x -> VerKeyDSIGN NeverDSIGN # | |||||
Generic (VerKeyDSIGN SchnorrSecp256k1DSIGN) | |||||
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Associated Types
Methods from :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x # to :: Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x -> VerKeyDSIGN SchnorrSecp256k1DSIGN # | |||||
Generic (VerKeyDSIGN ByronDSIGN) | |||||
Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN Associated Types
Methods from :: VerKeyDSIGN ByronDSIGN -> Rep (VerKeyDSIGN ByronDSIGN) x # to :: Rep (VerKeyDSIGN ByronDSIGN) x -> VerKeyDSIGN ByronDSIGN # | |||||
Generic (SigKES (CompactSingleKES d)) | |||||
Defined in Cardano.Crypto.KES.CompactSingle Associated Types
Methods from :: SigKES (CompactSingleKES d) -> Rep (SigKES (CompactSingleKES d)) x # to :: Rep (SigKES (CompactSingleKES d)) x -> SigKES (CompactSingleKES d) # | |||||
Generic (SigKES (CompactSumKES h d)) | |||||
Defined in Cardano.Crypto.KES.CompactSum Associated Types
Methods from :: SigKES (CompactSumKES h d) -> Rep (SigKES (CompactSumKES h d)) x # to :: Rep (SigKES (CompactSumKES h d)) x -> SigKES (CompactSumKES h d) # | |||||
Generic (SigKES (MockKES t)) | |||||
Defined in Cardano.Crypto.KES.Mock Associated Types
| |||||
Generic (SigKES NeverKES) | |||||
Defined in Cardano.Crypto.KES.NeverUsed | |||||
Generic (SigKES (SimpleKES d t)) | |||||
Defined in Cardano.Crypto.KES.Simple Associated Types
| |||||
Generic (SigKES (SingleKES d)) | |||||
Defined in Cardano.Crypto.KES.Single Associated Types
| |||||
Generic (SigKES (SumKES h d)) | |||||
Defined in Cardano.Crypto.KES.Sum Associated Types
| |||||
Generic (SignKeyKES (MockKES t)) | |||||
Defined in Cardano.Crypto.KES.Mock Associated Types
Methods from :: SignKeyKES (MockKES t) -> Rep (SignKeyKES (MockKES t)) x # to :: Rep (SignKeyKES (MockKES t)) x -> SignKeyKES (MockKES t) # | |||||
Generic (SignKeyKES NeverKES) | |||||
Defined in Cardano.Crypto.KES.NeverUsed Associated Types
Methods from :: SignKeyKES NeverKES -> Rep (SignKeyKES NeverKES) x # to :: Rep (SignKeyKES NeverKES) x -> SignKeyKES NeverKES # | |||||
Generic (SignKeyKES (SimpleKES d t)) | |||||
Defined in Cardano.Crypto.KES.Simple Associated Types
Methods from :: SignKeyKES (SimpleKES d t) -> Rep (SignKeyKES (SimpleKES d t)) x # to :: Rep (SignKeyKES (SimpleKES d t)) x -> SignKeyKES (SimpleKES d t) # | |||||
Generic (SignKeyWithPeriodKES v) | |||||
Defined in Cardano.Crypto.KES.Class Associated Types
Methods from :: SignKeyWithPeriodKES v -> Rep (SignKeyWithPeriodKES v) x # to :: Rep (SignKeyWithPeriodKES v) x -> SignKeyWithPeriodKES v # | |||||
Generic (UnsoundPureSignKeyKES (CompactSingleKES d)) | |||||
Defined in Cardano.Crypto.KES.CompactSingle Associated Types
Methods from :: UnsoundPureSignKeyKES (CompactSingleKES d) -> Rep (UnsoundPureSignKeyKES (CompactSingleKES d)) x # to :: Rep (UnsoundPureSignKeyKES (CompactSingleKES d)) x -> UnsoundPureSignKeyKES (CompactSingleKES d) # | |||||
Generic (UnsoundPureSignKeyKES (CompactSumKES h d)) | |||||
Defined in Cardano.Crypto.KES.CompactSum Associated Types
Methods from :: UnsoundPureSignKeyKES (CompactSumKES h d) -> Rep (UnsoundPureSignKeyKES (CompactSumKES h d)) x # to :: Rep (UnsoundPureSignKeyKES (CompactSumKES h d)) x -> UnsoundPureSignKeyKES (CompactSumKES h d) # | |||||
Generic (UnsoundPureSignKeyKES (MockKES t)) | |||||
Defined in Cardano.Crypto.KES.Mock Associated Types
Methods from :: UnsoundPureSignKeyKES (MockKES t) -> Rep (UnsoundPureSignKeyKES (MockKES t)) x # to :: Rep (UnsoundPureSignKeyKES (MockKES t)) x -> UnsoundPureSignKeyKES (MockKES t) # | |||||
Generic (UnsoundPureSignKeyKES NeverKES) | |||||
Defined in Cardano.Crypto.KES.NeverUsed Associated Types
Methods from :: UnsoundPureSignKeyKES NeverKES -> Rep (UnsoundPureSignKeyKES NeverKES) x # to :: Rep (UnsoundPureSignKeyKES NeverKES) x -> UnsoundPureSignKeyKES NeverKES # | |||||
Generic (UnsoundPureSignKeyKES (SimpleKES d t)) | |||||
Defined in Cardano.Crypto.KES.Simple Associated Types
Methods from :: UnsoundPureSignKeyKES (SimpleKES d t) -> Rep (UnsoundPureSignKeyKES (SimpleKES d t)) x # to :: Rep (UnsoundPureSignKeyKES (SimpleKES d t)) x -> UnsoundPureSignKeyKES (SimpleKES d t) # | |||||
Generic (UnsoundPureSignKeyKES (SingleKES d)) | |||||
Defined in Cardano.Crypto.KES.Single Associated Types
Methods from :: UnsoundPureSignKeyKES (SingleKES d) -> Rep (UnsoundPureSignKeyKES (SingleKES d)) x # to :: Rep (UnsoundPureSignKeyKES (SingleKES d)) x -> UnsoundPureSignKeyKES (SingleKES d) # | |||||
Generic (UnsoundPureSignKeyKES (SumKES h d)) | |||||
Defined in Cardano.Crypto.KES.Sum Associated Types
Methods from :: UnsoundPureSignKeyKES (SumKES h d) -> Rep (UnsoundPureSignKeyKES (SumKES h d)) x # to :: Rep (UnsoundPureSignKeyKES (SumKES h d)) x -> UnsoundPureSignKeyKES (SumKES h d) # | |||||
Generic (VerKeyKES (CompactSingleKES d)) | |||||
Defined in Cardano.Crypto.KES.CompactSingle Associated Types
Methods from :: VerKeyKES (CompactSingleKES d) -> Rep (VerKeyKES (CompactSingleKES d)) x # to :: Rep (VerKeyKES (CompactSingleKES d)) x -> VerKeyKES (CompactSingleKES d) # | |||||
Generic (VerKeyKES (CompactSumKES h d)) | |||||
Defined in Cardano.Crypto.KES.CompactSum Associated Types
Methods from :: VerKeyKES (CompactSumKES h d) -> Rep (VerKeyKES (CompactSumKES h d)) x # to :: Rep (VerKeyKES (CompactSumKES h d)) x -> VerKeyKES (CompactSumKES h d) # | |||||
Generic (VerKeyKES (MockKES t)) | |||||
Defined in Cardano.Crypto.KES.Mock Associated Types
| |||||
Generic (VerKeyKES NeverKES) | |||||
Defined in Cardano.Crypto.KES.NeverUsed Associated Types
| |||||
Generic (VerKeyKES (SimpleKES d t)) | |||||
Defined in Cardano.Crypto.KES.Simple Associated Types
| |||||
Generic (VerKeyKES (SingleKES d)) | |||||
Defined in Cardano.Crypto.KES.Single Associated Types
| |||||
Generic (VerKeyKES (SumKES h d)) | |||||
Defined in Cardano.Crypto.KES.Sum Associated Types
| |||||
Generic (CertVRF MockVRF) | |||||
Defined in Cardano.Crypto.VRF.Mock Associated Types
| |||||
Generic (CertVRF NeverVRF) | |||||
Defined in Cardano.Crypto.VRF.NeverUsed Associated Types
| |||||
Generic (CertVRF SimpleVRF) | |||||
Defined in Cardano.Crypto.VRF.Simple Associated Types
| |||||
Generic (CertVRF PraosVRF) | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic (CertVRF PraosBatchCompatVRF) | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
Methods from :: CertVRF PraosBatchCompatVRF -> Rep (CertVRF PraosBatchCompatVRF) x # to :: Rep (CertVRF PraosBatchCompatVRF) x -> CertVRF PraosBatchCompatVRF # | |||||
Generic (SignKeyVRF MockVRF) | |||||
Defined in Cardano.Crypto.VRF.Mock Associated Types
Methods from :: SignKeyVRF MockVRF -> Rep (SignKeyVRF MockVRF) x # to :: Rep (SignKeyVRF MockVRF) x -> SignKeyVRF MockVRF # | |||||
Generic (SignKeyVRF NeverVRF) | |||||
Defined in Cardano.Crypto.VRF.NeverUsed Associated Types
Methods from :: SignKeyVRF NeverVRF -> Rep (SignKeyVRF NeverVRF) x # to :: Rep (SignKeyVRF NeverVRF) x -> SignKeyVRF NeverVRF # | |||||
Generic (SignKeyVRF SimpleVRF) | |||||
Defined in Cardano.Crypto.VRF.Simple Associated Types
Methods from :: SignKeyVRF SimpleVRF -> Rep (SignKeyVRF SimpleVRF) x # to :: Rep (SignKeyVRF SimpleVRF) x -> SignKeyVRF SimpleVRF # | |||||
Generic (SignKeyVRF PraosVRF) | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
Methods from :: SignKeyVRF PraosVRF -> Rep (SignKeyVRF PraosVRF) x # to :: Rep (SignKeyVRF PraosVRF) x -> SignKeyVRF PraosVRF # | |||||
Generic (SignKeyVRF PraosBatchCompatVRF) | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
Methods from :: SignKeyVRF PraosBatchCompatVRF -> Rep (SignKeyVRF PraosBatchCompatVRF) x # to :: Rep (SignKeyVRF PraosBatchCompatVRF) x -> SignKeyVRF PraosBatchCompatVRF # | |||||
Generic (VerKeyVRF MockVRF) | |||||
Defined in Cardano.Crypto.VRF.Mock Associated Types
| |||||
Generic (VerKeyVRF NeverVRF) | |||||
Defined in Cardano.Crypto.VRF.NeverUsed Associated Types
| |||||
Generic (VerKeyVRF SimpleVRF) | |||||
Defined in Cardano.Crypto.VRF.Simple Associated Types
| |||||
Generic (VerKeyVRF PraosVRF) | |||||
Defined in Cardano.Crypto.VRF.Praos Associated Types
| |||||
Generic (VerKeyVRF PraosBatchCompatVRF) | |||||
Defined in Cardano.Crypto.VRF.PraosBatchCompat Associated Types
Methods from :: VerKeyVRF PraosBatchCompatVRF -> Rep (VerKeyVRF PraosBatchCompatVRF) x # to :: Rep (VerKeyVRF PraosBatchCompatVRF) x -> VerKeyVRF PraosBatchCompatVRF # | |||||
Generic (AProtocolMagic a) | |||||
Defined in Cardano.Crypto.ProtocolMagic Associated Types
Methods from :: AProtocolMagic a -> Rep (AProtocolMagic a) x # to :: Rep (AProtocolMagic a) x -> AProtocolMagic a # | |||||
Generic (RedeemSignature a) | |||||
Defined in Cardano.Crypto.Signing.Redeem.Signature Associated Types
Methods from :: RedeemSignature a -> Rep (RedeemSignature a) x # to :: Rep (RedeemSignature a) x -> RedeemSignature a # | |||||
Generic (Signature a) | |||||
Defined in Cardano.Crypto.Signing.Signature Associated Types
| |||||
Generic (OSet a) | |||||
Defined in Data.OSet.Strict Associated Types
| |||||
Generic (AllegraUtxoEvent era) | |||||
Defined in Cardano.Ledger.Allegra.Rules.Utxo Associated Types
Methods from :: AllegraUtxoEvent era -> Rep (AllegraUtxoEvent era) x # to :: Rep (AllegraUtxoEvent era) x -> AllegraUtxoEvent era # | |||||
Generic (AllegraUtxoPredFailure era) | |||||
Defined in Cardano.Ledger.Allegra.Rules.Utxo Associated Types
Methods from :: AllegraUtxoPredFailure era -> Rep (AllegraUtxoPredFailure era) x # to :: Rep (AllegraUtxoPredFailure era) x -> AllegraUtxoPredFailure era # | |||||
Generic (AllegraTxAuxData era) | |||||
Defined in Cardano.Ledger.Allegra.TxAuxData Associated Types
Methods from :: AllegraTxAuxData era -> Rep (AllegraTxAuxData era) x # to :: Rep (AllegraTxAuxData era) x -> AllegraTxAuxData era # | |||||
Generic (AllegraTxAuxDataRaw era) | |||||
Defined in Cardano.Ledger.Allegra.TxAuxData Associated Types
Methods from :: AllegraTxAuxDataRaw era -> Rep (AllegraTxAuxDataRaw era) x # to :: Rep (AllegraTxAuxDataRaw era) x -> AllegraTxAuxDataRaw era # | |||||
Generic (AllegraTxBody era) | |||||
Defined in Cardano.Ledger.Allegra.TxBody.Internal Associated Types
Methods from :: AllegraTxBody era -> Rep (AllegraTxBody era) x # to :: Rep (AllegraTxBody era) x -> AllegraTxBody era # | |||||
Generic (DowngradeAlonzoPParams f) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Associated Types
Methods from :: DowngradeAlonzoPParams f -> Rep (DowngradeAlonzoPParams f) x # to :: Rep (DowngradeAlonzoPParams f) x -> DowngradeAlonzoPParams f # | |||||
Generic (UpgradeAlonzoPParams f) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Associated Types
Methods from :: UpgradeAlonzoPParams f -> Rep (UpgradeAlonzoPParams f) x # to :: Rep (UpgradeAlonzoPParams f) x -> UpgradeAlonzoPParams f # | |||||
Generic (CollectError era) | |||||
Defined in Cardano.Ledger.Alonzo.Plutus.Evaluate Associated Types
Methods from :: CollectError era -> Rep (CollectError era) x # to :: Rep (CollectError era) x -> CollectError era # | |||||
Generic (AlonzoBbodyPredFailure era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Bbody Associated Types
Methods from :: AlonzoBbodyPredFailure era -> Rep (AlonzoBbodyPredFailure era) x # to :: Rep (AlonzoBbodyPredFailure era) x -> AlonzoBbodyPredFailure era # | |||||
Generic (AlonzoUtxoEvent era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxo Associated Types
Methods from :: AlonzoUtxoEvent era -> Rep (AlonzoUtxoEvent era) x # to :: Rep (AlonzoUtxoEvent era) x -> AlonzoUtxoEvent era # | |||||
Generic (AlonzoUtxoPredFailure era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxo Associated Types
Methods from :: AlonzoUtxoPredFailure era -> Rep (AlonzoUtxoPredFailure era) x # to :: Rep (AlonzoUtxoPredFailure era) x -> AlonzoUtxoPredFailure era # | |||||
Generic (AlonzoUtxosEvent era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Associated Types
Methods from :: AlonzoUtxosEvent era -> Rep (AlonzoUtxosEvent era) x # to :: Rep (AlonzoUtxosEvent era) x -> AlonzoUtxosEvent era # | |||||
Generic (AlonzoUtxosPredFailure era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Associated Types
Methods from :: AlonzoUtxosPredFailure era -> Rep (AlonzoUtxosPredFailure era) x # to :: Rep (AlonzoUtxosPredFailure era) x -> AlonzoUtxosPredFailure era # | |||||
Generic (AlonzoUtxowEvent era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxow Associated Types
Methods from :: AlonzoUtxowEvent era -> Rep (AlonzoUtxowEvent era) x # to :: Rep (AlonzoUtxowEvent era) x -> AlonzoUtxowEvent era # | |||||
Generic (AlonzoUtxowPredFailure era) | |||||
Defined in Cardano.Ledger.Alonzo.Rules.Utxow Associated Types
Methods from :: AlonzoUtxowPredFailure era -> Rep (AlonzoUtxowPredFailure era) x # to :: Rep (AlonzoUtxowPredFailure era) x -> AlonzoUtxowPredFailure era # | |||||
Generic (AlonzoScript era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods from :: AlonzoScript era -> Rep (AlonzoScript era) x # to :: Rep (AlonzoScript era) x -> AlonzoScript era # | |||||
Generic (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods from :: PlutusScript AlonzoEra -> Rep (PlutusScript AlonzoEra) x # to :: Rep (PlutusScript AlonzoEra) x -> PlutusScript AlonzoEra # | |||||
Generic (AlonzoTx era) | |||||
Defined in Cardano.Ledger.Alonzo.Tx Associated Types
| |||||
Generic (ScriptIntegrity era) | |||||
Defined in Cardano.Ledger.Alonzo.Tx Associated Types
Methods from :: ScriptIntegrity era -> Rep (ScriptIntegrity era) x # to :: Rep (ScriptIntegrity era) x -> ScriptIntegrity era # | |||||
Generic (AlonzoTxAuxData era) | |||||
Defined in Cardano.Ledger.Alonzo.TxAuxData Associated Types
Methods from :: AlonzoTxAuxData era -> Rep (AlonzoTxAuxData era) x # to :: Rep (AlonzoTxAuxData era) x -> AlonzoTxAuxData era # | |||||
Generic (AlonzoTxAuxDataRaw era) | |||||
Defined in Cardano.Ledger.Alonzo.TxAuxData Associated Types
Methods from :: AlonzoTxAuxDataRaw era -> Rep (AlonzoTxAuxDataRaw era) x # to :: Rep (AlonzoTxAuxDataRaw era) x -> AlonzoTxAuxDataRaw era # | |||||
Generic (AlonzoTxBody era) | |||||
Defined in Cardano.Ledger.Alonzo.TxBody.Internal Associated Types
Methods from :: AlonzoTxBody era -> Rep (AlonzoTxBody era) x # to :: Rep (AlonzoTxBody era) x -> AlonzoTxBody era # | |||||
Generic (AlonzoTxBodyRaw era) | |||||
Defined in Cardano.Ledger.Alonzo.TxBody.Internal Associated Types
Methods from :: AlonzoTxBodyRaw era -> Rep (AlonzoTxBodyRaw era) x # to :: Rep (AlonzoTxBodyRaw era) x -> AlonzoTxBodyRaw era # | |||||
Generic (AlonzoTxOut era) | |||||
Defined in Cardano.Ledger.Alonzo.TxOut Associated Types
Methods from :: AlonzoTxOut era -> Rep (AlonzoTxOut era) x # to :: Rep (AlonzoTxOut era) x -> AlonzoTxOut era # | |||||
Generic (AlonzoTxSeq era) | |||||
Defined in Cardano.Ledger.Alonzo.TxSeq.Internal Associated Types
Methods from :: AlonzoTxSeq era -> Rep (AlonzoTxSeq era) x # to :: Rep (AlonzoTxSeq era) x -> AlonzoTxSeq era # | |||||
Generic (AlonzoTxWits era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
Methods from :: AlonzoTxWits era -> Rep (AlonzoTxWits era) x # to :: Rep (AlonzoTxWits era) x -> AlonzoTxWits era # | |||||
Generic (AlonzoTxWitsRaw era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
Methods from :: AlonzoTxWitsRaw era -> Rep (AlonzoTxWitsRaw era) x # to :: Rep (AlonzoTxWitsRaw era) x -> AlonzoTxWitsRaw era # | |||||
Generic (Redeemers era) | |||||
Generic (RedeemersRaw era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
Methods from :: RedeemersRaw era -> Rep (RedeemersRaw era) x # to :: Rep (RedeemersRaw era) x -> RedeemersRaw era # | |||||
Generic (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
| |||||
Generic (TxDatsRaw era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
| |||||
Generic (BabbageUtxoPredFailure era) | |||||
Defined in Cardano.Ledger.Babbage.Rules.Utxo Associated Types
Methods from :: BabbageUtxoPredFailure era -> Rep (BabbageUtxoPredFailure era) x # to :: Rep (BabbageUtxoPredFailure era) x -> BabbageUtxoPredFailure era # | |||||
Generic (BabbageUtxowPredFailure era) | |||||
Defined in Cardano.Ledger.Babbage.Rules.Utxow Associated Types
Methods from :: BabbageUtxowPredFailure era -> Rep (BabbageUtxowPredFailure era) x # to :: Rep (BabbageUtxowPredFailure era) x -> BabbageUtxowPredFailure era # | |||||
Generic (BabbageTxBody era) | |||||
Defined in Cardano.Ledger.Babbage.TxBody.Internal Associated Types
Methods from :: BabbageTxBody era -> Rep (BabbageTxBody era) x # to :: Rep (BabbageTxBody era) x -> BabbageTxBody era # | |||||
Generic (BabbageTxBodyRaw era) | |||||
Defined in Cardano.Ledger.Babbage.TxBody.Internal Associated Types
Methods from :: BabbageTxBodyRaw era -> Rep (BabbageTxBodyRaw era) x # to :: Rep (BabbageTxBodyRaw era) x -> BabbageTxBodyRaw era # | |||||
Generic (BabbageContextError era) | |||||
Defined in Cardano.Ledger.Babbage.TxInfo Associated Types
Methods from :: BabbageContextError era -> Rep (BabbageContextError era) x # to :: Rep (BabbageContextError era) x -> BabbageContextError era # | |||||
Generic (BabbageTxOut era) | |||||
Defined in Cardano.Ledger.Babbage.TxOut Associated Types
Methods from :: BabbageTxOut era -> Rep (BabbageTxOut era) x # to :: Rep (BabbageTxOut era) x -> BabbageTxOut era # | |||||
Generic (Sized a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Sized Associated Types
| |||||
Generic (ABlock a) | |||||
Defined in Cardano.Chain.Block.Block Associated Types
| |||||
Generic (ABlockOrBoundary a) | |||||
Defined in Cardano.Chain.Block.Block Associated Types
Methods from :: ABlockOrBoundary a -> Rep (ABlockOrBoundary a) x # to :: Rep (ABlockOrBoundary a) x -> ABlockOrBoundary a # | |||||
Generic (ABlockOrBoundaryHdr a) | |||||
Defined in Cardano.Chain.Block.Block Associated Types
Methods from :: ABlockOrBoundaryHdr a -> Rep (ABlockOrBoundaryHdr a) x # to :: Rep (ABlockOrBoundaryHdr a) x -> ABlockOrBoundaryHdr a # | |||||
Generic (ABoundaryBlock a) | |||||
Defined in Cardano.Chain.Block.Block Associated Types
Methods from :: ABoundaryBlock a -> Rep (ABoundaryBlock a) x # to :: Rep (ABoundaryBlock a) x -> ABoundaryBlock a # | |||||
Generic (ABoundaryBody a) | |||||
Defined in Cardano.Chain.Block.Block Associated Types
Methods from :: ABoundaryBody a -> Rep (ABoundaryBody a) x # to :: Rep (ABoundaryBody a) x -> ABoundaryBody a # | |||||
Generic (ABody a) | |||||
Defined in Cardano.Chain.Block.Body Associated Types
| |||||
Generic (ABlockSignature a) | |||||
Defined in Cardano.Chain.Block.Header Associated Types
Methods from :: ABlockSignature a -> Rep (ABlockSignature a) x # to :: Rep (ABlockSignature a) x -> ABlockSignature a # | |||||
Generic (ABoundaryHeader a) | |||||
Defined in Cardano.Chain.Block.Header Associated Types
Methods from :: ABoundaryHeader a -> Rep (ABoundaryHeader a) x # to :: Rep (ABoundaryHeader a) x -> ABoundaryHeader a # | |||||
Generic (AHeader a) | |||||
Defined in Cardano.Chain.Block.Header Associated Types
| |||||
Generic (Attributes h) | |||||
Defined in Cardano.Chain.Common.Attributes Associated Types
| |||||
Generic (MerkleNode a) | |||||
Defined in Cardano.Chain.Common.Merkle Associated Types
| |||||
Generic (MerkleRoot a) | |||||
Defined in Cardano.Chain.Common.Merkle Associated Types
| |||||
Generic (MerkleTree a) | |||||
Defined in Cardano.Chain.Common.Merkle Associated Types
| |||||
Generic (ACertificate a) | |||||
Defined in Cardano.Chain.Delegation.Certificate Associated Types
Methods from :: ACertificate a -> Rep (ACertificate a) x # to :: Rep (ACertificate a) x -> ACertificate a # | |||||
Generic (APayload a) | |||||
Defined in Cardano.Chain.Delegation.Payload Associated Types
| |||||
Generic (ATxAux a) | |||||
Defined in Cardano.Chain.UTxO.TxAux Associated Types
| |||||
Generic (ATxPayload a) | |||||
Defined in Cardano.Chain.UTxO.TxPayload Associated Types
| |||||
Generic (APayload a) | |||||
Defined in Cardano.Chain.Update.Payload Associated Types
| |||||
Generic (AProposal a) | |||||
Defined in Cardano.Chain.Update.Proposal Associated Types
| |||||
Generic (AVote a) | |||||
Defined in Cardano.Chain.Update.Vote Associated Types
| |||||
Generic (ConwayGovState era) | |||||
Defined in Cardano.Ledger.Conway.Governance Associated Types
Methods from :: ConwayGovState era -> Rep (ConwayGovState era) x # to :: Rep (ConwayGovState era) x -> ConwayGovState era # | |||||
Generic (DRepPulsingState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.DRepPulser Associated Types
Methods from :: DRepPulsingState era -> Rep (DRepPulsingState era) x # to :: Rep (DRepPulsingState era) x -> DRepPulsingState era # | |||||
Generic (PulsingSnapshot era) | |||||
Defined in Cardano.Ledger.Conway.Governance.DRepPulser Associated Types
Methods from :: PulsingSnapshot era -> Rep (PulsingSnapshot era) x # to :: Rep (PulsingSnapshot era) x -> PulsingSnapshot era # | |||||
Generic (EnactState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Internal Associated Types
Methods from :: EnactState era -> Rep (EnactState era) x # to :: Rep (EnactState era) x -> EnactState era # | |||||
Generic (RatifyEnv era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Internal Associated Types
| |||||
Generic (RatifySignal era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Internal Associated Types
Methods from :: RatifySignal era -> Rep (RatifySignal era) x # to :: Rep (RatifySignal era) x -> RatifySignal era # | |||||
Generic (RatifyState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Internal Associated Types
Methods from :: RatifyState era -> Rep (RatifyState era) x # to :: Rep (RatifyState era) x -> RatifyState era # | |||||
Generic (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: Constitution era -> Rep (Constitution era) x # to :: Rep (Constitution era) x -> Constitution era # | |||||
Generic (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Generic (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovActionState era -> Rep (GovActionState era) x # to :: Rep (GovActionState era) x -> GovActionState era # | |||||
Generic (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: ProposalProcedure era -> Rep (ProposalProcedure era) x # to :: Rep (ProposalProcedure era) x -> ProposalProcedure era # | |||||
Generic (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: VotingProcedure era -> Rep (VotingProcedure era) x # to :: Rep (VotingProcedure era) x -> VotingProcedure era # | |||||
Generic (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: VotingProcedures era -> Rep (VotingProcedures era) x # to :: Rep (VotingProcedures era) x -> VotingProcedures era # | |||||
Generic (PEdges a) | |||||
Defined in Cardano.Ledger.Conway.Governance.Proposals Associated Types
| |||||
Generic (PGraph a) | |||||
Defined in Cardano.Ledger.Conway.Governance.Proposals Associated Types
| |||||
Generic (PRoot a) | |||||
Defined in Cardano.Ledger.Conway.Governance.Proposals Associated Types
| |||||
Generic (Proposals era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Proposals Associated Types
| |||||
Generic (UpgradeConwayPParams f) | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: UpgradeConwayPParams f -> Rep (UpgradeConwayPParams f) x # to :: Rep (UpgradeConwayPParams f) x -> UpgradeConwayPParams f # | |||||
Generic (ConwayBbodyPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Bbody Associated Types
Methods from :: ConwayBbodyPredFailure era -> Rep (ConwayBbodyPredFailure era) x # to :: Rep (ConwayBbodyPredFailure era) x -> ConwayBbodyPredFailure era # | |||||
Generic (CertEnv era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Cert Associated Types
| |||||
Generic (ConwayCertEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Cert Associated Types
Methods from :: ConwayCertEvent era -> Rep (ConwayCertEvent era) x # to :: Rep (ConwayCertEvent era) x -> ConwayCertEvent era # | |||||
Generic (ConwayCertPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Cert Associated Types
Methods from :: ConwayCertPredFailure era -> Rep (ConwayCertPredFailure era) x # to :: Rep (ConwayCertPredFailure era) x -> ConwayCertPredFailure era # | |||||
Generic (CertsEnv era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Certs Associated Types
| |||||
Generic (ConwayCertsEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Certs Associated Types
Methods from :: ConwayCertsEvent era -> Rep (ConwayCertsEvent era) x # to :: Rep (ConwayCertsEvent era) x -> ConwayCertsEvent era # | |||||
Generic (ConwayCertsPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Certs Associated Types
Methods from :: ConwayCertsPredFailure era -> Rep (ConwayCertsPredFailure era) x # to :: Rep (ConwayCertsPredFailure era) x -> ConwayCertsPredFailure era # | |||||
Generic (ConwayDelegEnv era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Deleg Associated Types
Methods from :: ConwayDelegEnv era -> Rep (ConwayDelegEnv era) x # to :: Rep (ConwayDelegEnv era) x -> ConwayDelegEnv era # | |||||
Generic (ConwayDelegPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Deleg Associated Types
Methods from :: ConwayDelegPredFailure era -> Rep (ConwayDelegPredFailure era) x # to :: Rep (ConwayDelegPredFailure era) x -> ConwayDelegPredFailure era # | |||||
Generic (EnactSignal era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Enact Associated Types
Methods from :: EnactSignal era -> Rep (EnactSignal era) x # to :: Rep (EnactSignal era) x -> EnactSignal era # | |||||
Generic (ConwayEpochEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Epoch Associated Types
Methods from :: ConwayEpochEvent era -> Rep (ConwayEpochEvent era) x # to :: Rep (ConwayEpochEvent era) x -> ConwayEpochEvent era # | |||||
Generic (ConwayGovEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Gov Associated Types
Methods from :: ConwayGovEvent era -> Rep (ConwayGovEvent era) x # to :: Rep (ConwayGovEvent era) x -> ConwayGovEvent era # | |||||
Generic (ConwayGovPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Gov Associated Types
Methods from :: ConwayGovPredFailure era -> Rep (ConwayGovPredFailure era) x # to :: Rep (ConwayGovPredFailure era) x -> ConwayGovPredFailure era # | |||||
Generic (GovEnv era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Gov Associated Types
| |||||
Generic (GovSignal era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Gov Associated Types
| |||||
Generic (ConwayGovCertEnv era) | |||||
Defined in Cardano.Ledger.Conway.Rules.GovCert Associated Types
Methods from :: ConwayGovCertEnv era -> Rep (ConwayGovCertEnv era) x # to :: Rep (ConwayGovCertEnv era) x -> ConwayGovCertEnv era # | |||||
Generic (ConwayGovCertPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.GovCert Associated Types
Methods from :: ConwayGovCertPredFailure era -> Rep (ConwayGovCertPredFailure era) x # to :: Rep (ConwayGovCertPredFailure era) x -> ConwayGovCertPredFailure era # | |||||
Generic (ConwayHardForkEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.HardFork Associated Types
Methods from :: ConwayHardForkEvent era -> Rep (ConwayHardForkEvent era) x # to :: Rep (ConwayHardForkEvent era) x -> ConwayHardForkEvent era # | |||||
Generic (ConwayLedgerEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Ledger Associated Types
Methods from :: ConwayLedgerEvent era -> Rep (ConwayLedgerEvent era) x # to :: Rep (ConwayLedgerEvent era) x -> ConwayLedgerEvent era # | |||||
Generic (ConwayLedgerPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Ledger Associated Types
Methods from :: ConwayLedgerPredFailure era -> Rep (ConwayLedgerPredFailure era) x # to :: Rep (ConwayLedgerPredFailure era) x -> ConwayLedgerPredFailure era # | |||||
Generic (ConwayNewEpochEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.NewEpoch Associated Types
Methods from :: ConwayNewEpochEvent era -> Rep (ConwayNewEpochEvent era) x # to :: Rep (ConwayNewEpochEvent era) x -> ConwayNewEpochEvent era # | |||||
Generic (ConwayNewEpochPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.NewEpoch Associated Types
Methods from :: ConwayNewEpochPredFailure era -> Rep (ConwayNewEpochPredFailure era) x # to :: Rep (ConwayNewEpochPredFailure era) x -> ConwayNewEpochPredFailure era # | |||||
Generic (ConwayTickfPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Tickf Associated Types
Methods from :: ConwayTickfPredFailure era -> Rep (ConwayTickfPredFailure era) x # to :: Rep (ConwayTickfPredFailure era) x -> ConwayTickfPredFailure era # | |||||
Generic (ConwayUtxoPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Utxo Associated Types
Methods from :: ConwayUtxoPredFailure era -> Rep (ConwayUtxoPredFailure era) x # to :: Rep (ConwayUtxoPredFailure era) x -> ConwayUtxoPredFailure era # | |||||
Generic (ConwayUtxosEvent era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Utxos Associated Types
Methods from :: ConwayUtxosEvent era -> Rep (ConwayUtxosEvent era) x # to :: Rep (ConwayUtxosEvent era) x -> ConwayUtxosEvent era # | |||||
Generic (ConwayUtxosPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Utxos Associated Types
Methods from :: ConwayUtxosPredFailure era -> Rep (ConwayUtxosPredFailure era) x # to :: Rep (ConwayUtxosPredFailure era) x -> ConwayUtxosPredFailure era # | |||||
Generic (ConwayUtxowPredFailure era) | |||||
Defined in Cardano.Ledger.Conway.Rules.Utxow Associated Types
Methods from :: ConwayUtxowPredFailure era -> Rep (ConwayUtxowPredFailure era) x # to :: Rep (ConwayUtxowPredFailure era) x -> ConwayUtxowPredFailure era # | |||||
Generic (ConwayInstantStake era) | |||||
Defined in Cardano.Ledger.Conway.State.Stake Associated Types
Methods from :: ConwayInstantStake era -> Rep (ConwayInstantStake era) x # to :: Rep (ConwayInstantStake era) x -> ConwayInstantStake era # | |||||
Generic (ConwayTxBody era) | |||||
Defined in Cardano.Ledger.Conway.TxBody.Internal Associated Types
Methods from :: ConwayTxBody era -> Rep (ConwayTxBody era) x # to :: Rep (ConwayTxBody era) x -> ConwayTxBody era # | |||||
Generic (ConwayTxBodyRaw era) | |||||
Defined in Cardano.Ledger.Conway.TxBody.Internal Associated Types
Methods from :: ConwayTxBodyRaw era -> Rep (ConwayTxBodyRaw era) x # to :: Rep (ConwayTxBodyRaw era) x -> ConwayTxBodyRaw era # | |||||
Generic (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
Methods from :: ConwayTxCert era -> Rep (ConwayTxCert era) x # to :: Rep (ConwayTxCert era) x -> ConwayTxCert era # | |||||
Generic (ConwayContextError era) | |||||
Defined in Cardano.Ledger.Conway.TxInfo Associated Types
Methods from :: ConwayContextError era -> Rep (ConwayContextError era) x # to :: Rep (ConwayContextError era) x -> ConwayContextError era # | |||||
Generic (CommitteeState era) | |||||
Defined in Cardano.Ledger.CertState Associated Types
Methods from :: CommitteeState era -> Rep (CommitteeState era) x # to :: Rep (CommitteeState era) x -> CommitteeState era # | |||||
Generic (DState era) | |||||
Defined in Cardano.Ledger.CertState Associated Types
| |||||
Generic (PState era) | |||||
Defined in Cardano.Ledger.CertState Associated Types
| |||||
Generic (VState era) | |||||
Defined in Cardano.Ledger.CertState Associated Types
| |||||
Generic (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
| |||||
Generic (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
Methods from :: PParamsUpdate era -> Rep (PParamsUpdate era) x # to :: Rep (PParamsUpdate era) x -> PParamsUpdate era # | |||||
Generic (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Associated Types
Methods from :: Credential kr -> Rep (Credential kr) x # to :: Rep (Credential kr) x -> Credential kr # | |||||
Generic (NoUpdate a) | |||||
Defined in Cardano.Ledger.HKD | |||||
Generic (KeyHash r) | |||||
Generic (VRFVerKeyHash r) | |||||
Defined in Cardano.Ledger.Hashes Associated Types
Methods from :: VRFVerKeyHash r -> Rep (VRFVerKeyHash r) x # to :: Rep (VRFVerKeyHash r) x -> VRFVerKeyHash r # | |||||
Generic (VKey kd) | |||||
Defined in Cardano.Ledger.Keys.Internal Associated Types
| |||||
Generic (WitVKey kr) | |||||
Defined in Cardano.Ledger.Keys.WitVKey Associated Types
| |||||
Generic (MemoBytes t) | |||||
Defined in Cardano.Ledger.MemoBytes.Internal Associated Types
| |||||
Generic (BinaryData era) | |||||
Defined in Cardano.Ledger.Plutus.Data Associated Types
Methods from :: BinaryData era -> Rep (BinaryData era) x # to :: Rep (BinaryData era) x -> BinaryData era # | |||||
Generic (Data era) | |||||
Defined in Cardano.Ledger.Plutus.Data Associated Types
| |||||
Generic (Datum era) | |||||
Defined in Cardano.Ledger.Plutus.Data Associated Types
| |||||
Generic (PlutusData era) | |||||
Defined in Cardano.Ledger.Plutus.Data Associated Types
Methods from :: PlutusData era -> Rep (PlutusData era) x # to :: Rep (PlutusData era) x -> PlutusData era # | |||||
Generic (ExUnits' a) | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Associated Types
| |||||
Generic (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
| |||||
Generic (PlutusRunnable l) | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
Methods from :: PlutusRunnable l -> Rep (PlutusRunnable l) x # to :: Rep (PlutusRunnable l) x -> PlutusRunnable l # | |||||
Generic (FuturePParams era) | |||||
Defined in Cardano.Ledger.State.Governance Associated Types
Methods from :: FuturePParams era -> Rep (FuturePParams era) x # to :: Rep (FuturePParams era) x -> FuturePParams era # | |||||
Generic (ScriptsProvided era) | |||||
Defined in Cardano.Ledger.State.UTxO Associated Types
Methods from :: ScriptsProvided era -> Rep (ScriptsProvided era) x # to :: Rep (ScriptsProvided era) x -> ScriptsProvided era # | |||||
Generic (UTxO era) | |||||
Defined in Cardano.Ledger.State.UTxO Associated Types
| |||||
Generic (KeyPair kd) | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Associated Types
| |||||
Generic (MaryTxBody era) | |||||
Defined in Cardano.Ledger.Mary.TxBody.Internal Associated Types
Methods from :: MaryTxBody era -> Rep (MaryTxBody era) x # to :: Rep (MaryTxBody era) x -> MaryTxBody era # | |||||
Generic (MaryTxBodyRaw era) | |||||
Defined in Cardano.Ledger.Mary.TxBody.Internal Associated Types
Methods from :: MaryTxBodyRaw era -> Rep (MaryTxBodyRaw era) x # to :: Rep (MaryTxBodyRaw era) x -> MaryTxBodyRaw era # | |||||
Generic (BlockTransitionError era) | |||||
Defined in Cardano.Ledger.Shelley.API.Validation Associated Types
Methods from :: BlockTransitionError era -> Rep (BlockTransitionError era) x # to :: Rep (BlockTransitionError era) x -> BlockTransitionError era # | |||||
Generic (TickTransitionError era) | |||||
Defined in Cardano.Ledger.Shelley.API.Validation Associated Types
Methods from :: TickTransitionError era -> Rep (TickTransitionError era) x # to :: Rep (TickTransitionError era) x -> TickTransitionError era # | |||||
Generic (ShelleyTxSeq era) | |||||
Defined in Cardano.Ledger.Shelley.BlockChain Associated Types
Methods from :: ShelleyTxSeq era -> Rep (ShelleyTxSeq era) x # to :: Rep (ShelleyTxSeq era) x -> ShelleyTxSeq era # | |||||
Generic (ShelleyCertState era) | |||||
Defined in Cardano.Ledger.Shelley.CertState Associated Types
Methods from :: ShelleyCertState era -> Rep (ShelleyCertState era) x # to :: Rep (ShelleyCertState era) x -> ShelleyCertState era # | |||||
Generic (ShelleyGovState era) | |||||
Defined in Cardano.Ledger.Shelley.Governance Associated Types
Methods from :: ShelleyGovState era -> Rep (ShelleyGovState era) x # to :: Rep (ShelleyGovState era) x -> ShelleyGovState era # | |||||
Generic (EpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Associated Types
Methods from :: EpochState era -> Rep (EpochState era) x # to :: Rep (EpochState era) x -> EpochState era # | |||||
Generic (LedgerState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Associated Types
Methods from :: LedgerState era -> Rep (LedgerState era) x # to :: Rep (LedgerState era) x -> LedgerState era # | |||||
Generic (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Associated Types
Methods from :: NewEpochState era -> Rep (NewEpochState era) x # to :: Rep (NewEpochState era) x -> NewEpochState era # | |||||
Generic (UTxOState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Associated Types
| |||||
Generic (ProposedPPUpdates era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Associated Types
Methods from :: ProposedPPUpdates era -> Rep (ProposedPPUpdates era) x # to :: Rep (ProposedPPUpdates era) x -> ProposedPPUpdates era # | |||||
Generic (Update era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Associated Types
| |||||
Generic (ShelleyBbodyPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Associated Types
Methods from :: ShelleyBbodyPredFailure era -> Rep (ShelleyBbodyPredFailure era) x # to :: Rep (ShelleyBbodyPredFailure era) x -> ShelleyBbodyPredFailure era # | |||||
Generic (DelegEnv era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
| |||||
Generic (ShelleyDelegEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
Methods from :: ShelleyDelegEvent era -> Rep (ShelleyDelegEvent era) x # to :: Rep (ShelleyDelegEvent era) x -> ShelleyDelegEvent era # | |||||
Generic (ShelleyDelegPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
Methods from :: ShelleyDelegPredFailure era -> Rep (ShelleyDelegPredFailure era) x # to :: Rep (ShelleyDelegPredFailure era) x -> ShelleyDelegPredFailure era # | |||||
Generic (ShelleyDelegsEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Associated Types
Methods from :: ShelleyDelegsEvent era -> Rep (ShelleyDelegsEvent era) x # to :: Rep (ShelleyDelegsEvent era) x -> ShelleyDelegsEvent era # | |||||
Generic (ShelleyDelegsPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Associated Types
Methods from :: ShelleyDelegsPredFailure era -> Rep (ShelleyDelegsPredFailure era) x # to :: Rep (ShelleyDelegsPredFailure era) x -> ShelleyDelegsPredFailure era # | |||||
Generic (ShelleyDelplEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Associated Types
Methods from :: ShelleyDelplEvent era -> Rep (ShelleyDelplEvent era) x # to :: Rep (ShelleyDelplEvent era) x -> ShelleyDelplEvent era # | |||||
Generic (ShelleyDelplPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Associated Types
Methods from :: ShelleyDelplPredFailure era -> Rep (ShelleyDelplPredFailure era) x # to :: Rep (ShelleyDelplPredFailure era) x -> ShelleyDelplPredFailure era # | |||||
Generic (ShelleyEpochEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Associated Types
Methods from :: ShelleyEpochEvent era -> Rep (ShelleyEpochEvent era) x # to :: Rep (ShelleyEpochEvent era) x -> ShelleyEpochEvent era # | |||||
Generic (ShelleyEpochPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Associated Types
Methods from :: ShelleyEpochPredFailure era -> Rep (ShelleyEpochPredFailure era) x # to :: Rep (ShelleyEpochPredFailure era) x -> ShelleyEpochPredFailure era # | |||||
Generic (LedgerEnv era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
| |||||
Generic (ShelleyLedgerEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
Methods from :: ShelleyLedgerEvent era -> Rep (ShelleyLedgerEvent era) x # to :: Rep (ShelleyLedgerEvent era) x -> ShelleyLedgerEvent era # | |||||
Generic (ShelleyLedgerPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
Methods from :: ShelleyLedgerPredFailure era -> Rep (ShelleyLedgerPredFailure era) x # to :: Rep (ShelleyLedgerPredFailure era) x -> ShelleyLedgerPredFailure era # | |||||
Generic (ShelleyLedgersEnv era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods from :: ShelleyLedgersEnv era -> Rep (ShelleyLedgersEnv era) x # to :: Rep (ShelleyLedgersEnv era) x -> ShelleyLedgersEnv era # | |||||
Generic (ShelleyLedgersPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods from :: ShelleyLedgersPredFailure era -> Rep (ShelleyLedgersPredFailure era) x # to :: Rep (ShelleyLedgersPredFailure era) x -> ShelleyLedgersPredFailure era # | |||||
Generic (ShelleyMirEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Associated Types
Methods from :: ShelleyMirEvent era -> Rep (ShelleyMirEvent era) x # to :: Rep (ShelleyMirEvent era) x -> ShelleyMirEvent era # | |||||
Generic (ShelleyMirPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Associated Types
Methods from :: ShelleyMirPredFailure era -> Rep (ShelleyMirPredFailure era) x # to :: Rep (ShelleyMirPredFailure era) x -> ShelleyMirPredFailure era # | |||||
Generic (ShelleyNewEpochEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Associated Types
Methods from :: ShelleyNewEpochEvent era -> Rep (ShelleyNewEpochEvent era) x # to :: Rep (ShelleyNewEpochEvent era) x -> ShelleyNewEpochEvent era # | |||||
Generic (ShelleyNewEpochPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Associated Types
Methods from :: ShelleyNewEpochPredFailure era -> Rep (ShelleyNewEpochPredFailure era) x # to :: Rep (ShelleyNewEpochPredFailure era) x -> ShelleyNewEpochPredFailure era # | |||||
Generic (PoolEnv era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
| |||||
Generic (PoolEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
| |||||
Generic (ShelleyPoolPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
Methods from :: ShelleyPoolPredFailure era -> Rep (ShelleyPoolPredFailure era) x # to :: Rep (ShelleyPoolPredFailure era) x -> ShelleyPoolPredFailure era # | |||||
Generic (ShelleyPoolreapEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Associated Types
Methods from :: ShelleyPoolreapEvent era -> Rep (ShelleyPoolreapEvent era) x # to :: Rep (ShelleyPoolreapEvent era) x -> ShelleyPoolreapEvent era # | |||||
Generic (ShelleyPoolreapPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Associated Types
Methods from :: ShelleyPoolreapPredFailure era -> Rep (ShelleyPoolreapPredFailure era) x # to :: Rep (ShelleyPoolreapPredFailure era) x -> ShelleyPoolreapPredFailure era # | |||||
Generic (PpupEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
| |||||
Generic (ShelleyPpupPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
Methods from :: ShelleyPpupPredFailure era -> Rep (ShelleyPpupPredFailure era) x # to :: Rep (ShelleyPpupPredFailure era) x -> ShelleyPpupPredFailure era # | |||||
Generic (ShelleyRupdPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd Associated Types
Methods from :: ShelleyRupdPredFailure era -> Rep (ShelleyRupdPredFailure era) x # to :: Rep (ShelleyRupdPredFailure era) x -> ShelleyRupdPredFailure era # | |||||
Generic (ShelleySnapPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Snap Associated Types
Methods from :: ShelleySnapPredFailure era -> Rep (ShelleySnapPredFailure era) x # to :: Rep (ShelleySnapPredFailure era) x -> ShelleySnapPredFailure era # | |||||
Generic (SnapEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Snap Associated Types
| |||||
Generic (ShelleyTickEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods from :: ShelleyTickEvent era -> Rep (ShelleyTickEvent era) x # to :: Rep (ShelleyTickEvent era) x -> ShelleyTickEvent era # | |||||
Generic (ShelleyTickPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods from :: ShelleyTickPredFailure era -> Rep (ShelleyTickPredFailure era) x # to :: Rep (ShelleyTickPredFailure era) x -> ShelleyTickPredFailure era # | |||||
Generic (ShelleyTickfPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods from :: ShelleyTickfPredFailure era -> Rep (ShelleyTickfPredFailure era) x # to :: Rep (ShelleyTickfPredFailure era) x -> ShelleyTickfPredFailure era # | |||||
Generic (ShelleyUpecPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Upec Associated Types
Methods from :: ShelleyUpecPredFailure era -> Rep (ShelleyUpecPredFailure era) x # to :: Rep (ShelleyUpecPredFailure era) x -> ShelleyUpecPredFailure era # | |||||
Generic (ShelleyUtxoPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
Methods from :: ShelleyUtxoPredFailure era -> Rep (ShelleyUtxoPredFailure era) x # to :: Rep (ShelleyUtxoPredFailure era) x -> ShelleyUtxoPredFailure era # | |||||
Generic (UtxoEnv era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
| |||||
Generic (UtxoEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
| |||||
Generic (ShelleyUtxowEvent era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Associated Types
Methods from :: ShelleyUtxowEvent era -> Rep (ShelleyUtxowEvent era) x # to :: Rep (ShelleyUtxowEvent era) x -> ShelleyUtxowEvent era # | |||||
Generic (ShelleyUtxowPredFailure era) | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Associated Types
Methods from :: ShelleyUtxowPredFailure era -> Rep (ShelleyUtxowPredFailure era) x # to :: Rep (ShelleyUtxowPredFailure era) x -> ShelleyUtxowPredFailure era # | |||||
Generic (MultiSig era) | |||||
Defined in Cardano.Ledger.Shelley.Scripts Associated Types
| |||||
Generic (MultiSigRaw era) | |||||
Defined in Cardano.Ledger.Shelley.Scripts Associated Types
Methods from :: MultiSigRaw era -> Rep (MultiSigRaw era) x # to :: Rep (MultiSigRaw era) x -> MultiSigRaw era # | |||||
Generic (ShelleyInstantStake era) | |||||
Defined in Cardano.Ledger.Shelley.State.Stake Associated Types
Methods from :: ShelleyInstantStake era -> Rep (ShelleyInstantStake era) x # to :: Rep (ShelleyInstantStake era) x -> ShelleyInstantStake era # | |||||
Generic (TransitionConfig ShelleyEra) | |||||
Defined in Cardano.Ledger.Shelley.Transition Associated Types
Methods from :: TransitionConfig ShelleyEra -> Rep (TransitionConfig ShelleyEra) x # to :: Rep (TransitionConfig ShelleyEra) x -> TransitionConfig ShelleyEra # | |||||
Generic (ShelleyTx era) | |||||
Defined in Cardano.Ledger.Shelley.Tx.Internal Associated Types
| |||||
Generic (ShelleyTxRaw era) | |||||
Defined in Cardano.Ledger.Shelley.Tx.Internal Associated Types
Methods from :: ShelleyTxRaw era -> Rep (ShelleyTxRaw era) x # to :: Rep (ShelleyTxRaw era) x -> ShelleyTxRaw era # | |||||
Generic (ShelleyTxAuxData era) | |||||
Defined in Cardano.Ledger.Shelley.TxAuxData Associated Types
Methods from :: ShelleyTxAuxData era -> Rep (ShelleyTxAuxData era) x # to :: Rep (ShelleyTxAuxData era) x -> ShelleyTxAuxData era # | |||||
Generic (ShelleyTxAuxDataRaw era) | |||||
Defined in Cardano.Ledger.Shelley.TxAuxData Associated Types
Methods from :: ShelleyTxAuxDataRaw era -> Rep (ShelleyTxAuxDataRaw era) x # to :: Rep (ShelleyTxAuxDataRaw era) x -> ShelleyTxAuxDataRaw era # | |||||
Generic (ShelleyTxBody era) | |||||
Defined in Cardano.Ledger.Shelley.TxBody Associated Types
Methods from :: ShelleyTxBody era -> Rep (ShelleyTxBody era) x # to :: Rep (ShelleyTxBody era) x -> ShelleyTxBody era # | |||||
Generic (ShelleyTxBodyRaw era) | |||||
Defined in Cardano.Ledger.Shelley.TxBody Associated Types
Methods from :: ShelleyTxBodyRaw era -> Rep (ShelleyTxBodyRaw era) x # to :: Rep (ShelleyTxBodyRaw era) x -> ShelleyTxBodyRaw era # | |||||
Generic (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: ShelleyTxCert era -> Rep (ShelleyTxCert era) x # to :: Rep (ShelleyTxCert era) x -> ShelleyTxCert era # | |||||
Generic (ShelleyTxWits era) | |||||
Defined in Cardano.Ledger.Shelley.TxWits Associated Types
Methods from :: ShelleyTxWits era -> Rep (ShelleyTxWits era) x # to :: Rep (ShelleyTxWits era) x -> ShelleyTxWits era # | |||||
Generic (ShelleyTxWitsRaw era) | |||||
Defined in Cardano.Ledger.Shelley.TxWits Associated Types
Methods from :: ShelleyTxWitsRaw era -> Rep (ShelleyTxWitsRaw era) x # to :: Rep (ShelleyTxWitsRaw era) x -> ShelleyTxWitsRaw era # | |||||
Generic (ChainTransitionError c) | |||||
Defined in Cardano.Protocol.TPraos.API Associated Types
Methods from :: ChainTransitionError c -> Rep (ChainTransitionError c) x # to :: Rep (ChainTransitionError c) x -> ChainTransitionError c # | |||||
Generic (BHBody c) | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
| |||||
Generic (BHeader c) | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
| |||||
Generic (BHeaderRaw c) | |||||
Defined in Cardano.Protocol.TPraos.BHeader Associated Types
| |||||
Generic (OCert c) | |||||
Defined in Cardano.Protocol.TPraos.OCert Associated Types
| |||||
Generic (OverlayPredicateFailure c) | |||||
Defined in Cardano.Protocol.TPraos.Rules.Overlay Associated Types
Methods from :: OverlayPredicateFailure c -> Rep (OverlayPredicateFailure c) x # to :: Rep (OverlayPredicateFailure c) x -> OverlayPredicateFailure c # | |||||
Generic (PrtclPredicateFailure c) | |||||
Defined in Cardano.Protocol.TPraos.Rules.Prtcl Associated Types
Methods from :: PrtclPredicateFailure c -> Rep (PrtclPredicateFailure c) x # to :: Rep (PrtclPredicateFailure c) x -> PrtclPredicateFailure c # | |||||
Generic (UpdnPredicateFailure c) | |||||
Defined in Cardano.Protocol.TPraos.Rules.Updn Associated Types
Methods from :: UpdnPredicateFailure c -> Rep (UpdnPredicateFailure c) x # to :: Rep (UpdnPredicateFailure c) x -> UpdnPredicateFailure c # | |||||
Generic (WithOrigin t) | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Generic (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Associated Types
Methods from :: StrictMaybe a -> Rep (StrictMaybe a) x # to :: Rep (StrictMaybe a) x -> StrictMaybe a # | |||||
Generic (SCC vertex) | |||||
Defined in Data.Graph Associated Types
| |||||
Generic (Digit a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Elem a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (FingerTree a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Node a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (ViewL a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (ViewR a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
Generic (Tree a) | |||||
Defined in Data.Tree Associated Types
| |||||
Generic (Fix f) | |||||
Generic (Basename a) | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Generic (Relative a) | |||||
Defined in System.Directory.OsPath.Types Associated Types
| |||||
Generic (Digit a) | |||||
Defined in Data.FingerTree Associated Types
| |||||
Generic (PostAligned a) | |||||
Defined in Flat.Filler Associated Types
Methods from :: PostAligned a -> Rep (PostAligned a) x # to :: Rep (PostAligned a) x -> PostAligned a # | |||||
Generic (PreAligned a) | |||||
Defined in Flat.Filler Associated Types
| |||||
Generic (Handle h) | |||||
Defined in System.FS.API.Types Associated Types
| |||||
Generic a => Generic (FiniteEnumeration a) | |||||
Defined in Generic.Data.Internal.Generically Associated Types
Methods from :: FiniteEnumeration a -> Rep (FiniteEnumeration a) x # to :: Rep (FiniteEnumeration a) x -> FiniteEnumeration a # | |||||
Generic a => Generic (GenericProduct a) | |||||
Defined in Generic.Data.Internal.Generically Associated Types
Methods from :: GenericProduct a -> Rep (GenericProduct a) x # to :: Rep (GenericProduct a) x -> GenericProduct a # | |||||
Generic (GenClosure b) | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
| |||||
Generic (GenStackField b) | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
Methods from :: GenStackField b -> Rep (GenStackField b) x # to :: Rep (GenStackField b) x -> GenStackField b # | |||||
Generic (GenStackFrame b) | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
Methods from :: GenStackFrame b -> Rep (GenStackFrame b) x # to :: Rep (GenStackFrame b) x -> GenStackFrame b # | |||||
Generic (GenStgStackClosure b) | |||||
Defined in GHC.Exts.Heap.Closures Associated Types
Methods from :: GenStgStackClosure b -> Rep (GenStgStackClosure b) x # to :: Rep (GenStgStackClosure b) x -> GenStgStackClosure b # | |||||
Generic (NonEmpty a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Identity a) | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
Generic (First a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Last a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Down a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Dual a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Endo a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Product a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Sum a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (ZipList a) | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
Generic (Par1 p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (HistoriedResponse body) | |||||
Defined in Network.HTTP.Client Associated Types
Methods from :: HistoriedResponse body -> Rep (HistoriedResponse body) x # to :: Rep (HistoriedResponse body) x -> HistoriedResponse body # | |||||
Generic (Resources a) | |||||
Defined in Cardano.BM.Stats.Resources Associated Types
| |||||
Generic (AddrRange a) | |||||
Defined in Data.IP.Range Associated Types
| |||||
Generic (Item a) | |||||
Defined in Katip.Core Associated Types
| |||||
Generic (MaestroApiV1 route) | |||||
Defined in Maestro.API.V1 Associated Types
Methods from :: MaestroApiV1 route -> Rep (MaestroApiV1 route) x # to :: Rep (MaestroApiV1 route) x -> MaestroApiV1 route # | |||||
Generic (MaestroApiV1Auth route) | |||||
Defined in Maestro.API.V1 Associated Types
Methods from :: MaestroApiV1Auth route -> Rep (MaestroApiV1Auth route) x # to :: Rep (MaestroApiV1Auth route) x -> MaestroApiV1Auth route # | |||||
Generic (AccountsAPI route) | |||||
Defined in Maestro.API.V1.Accounts Associated Types
Methods from :: AccountsAPI route -> Rep (AccountsAPI route) x # to :: Rep (AccountsAPI route) x -> AccountsAPI route # | |||||
Generic (AddressesAPI route) | |||||
Defined in Maestro.API.V1.Addresses Associated Types
Methods from :: AddressesAPI route -> Rep (AddressesAPI route) x # to :: Rep (AddressesAPI route) x -> AddressesAPI route # | |||||
Generic (AssetsAPI route) | |||||
Defined in Maestro.API.V1.Assets Associated Types
| |||||
Generic (BlocksAPI route) | |||||
Defined in Maestro.API.V1.Blocks Associated Types
| |||||
Generic (DatumAPI route) | |||||
Defined in Maestro.API.V1.Datum Associated Types
| |||||
Generic (DefiMarketsAPI route) | |||||
Defined in Maestro.API.V1.DefiMarkets Associated Types
Methods from :: DefiMarketsAPI route -> Rep (DefiMarketsAPI route) x # to :: Rep (DefiMarketsAPI route) x -> DefiMarketsAPI route # | |||||
Generic (GeneralAPI route) | |||||
Defined in Maestro.API.V1.General Associated Types
Methods from :: GeneralAPI route -> Rep (GeneralAPI route) x # to :: Rep (GeneralAPI route) x -> GeneralAPI route # | |||||
Generic (PoolsAPI route) | |||||
Defined in Maestro.API.V1.Pools Associated Types
| |||||
Generic (TransactionsAPI route) | |||||
Defined in Maestro.API.V1.Transactions Associated Types
Methods from :: TransactionsAPI route -> Rep (TransactionsAPI route) x # to :: Rep (TransactionsAPI route) x -> TransactionsAPI route # | |||||
Generic (TxManagerAPI route) | |||||
Defined in Maestro.API.V1.TxManager Associated Types
Methods from :: TxManagerAPI route -> Rep (TxManagerAPI route) x # to :: Rep (TxManagerAPI route) x -> TxManagerAPI route # | |||||
Generic (Bech32StringOf a) | |||||
Defined in Maestro.Types.Common Associated Types
Methods from :: Bech32StringOf a -> Rep (Bech32StringOf a) x # to :: Rep (Bech32StringOf a) x -> Bech32StringOf a # | |||||
Generic (HashStringOf a) | |||||
Defined in Maestro.Types.Common Associated Types
Methods from :: HashStringOf a -> Rep (HashStringOf a) x # to :: Rep (HashStringOf a) x -> HashStringOf a # | |||||
Generic (HexStringOf a) | |||||
Defined in Maestro.Types.Common Associated Types
Methods from :: HexStringOf a -> Rep (HexStringOf a) x # to :: Rep (HexStringOf a) x -> HexStringOf a # | |||||
Generic (TaggedText description) | |||||
Defined in Maestro.Types.V1.Common Associated Types
Methods from :: TaggedText description -> Rep (TaggedText description) x # to :: Rep (TaggedText description) x -> TaggedText description # | |||||
Generic (MemoryCpuWith i) | |||||
Defined in Maestro.Types.V1.General Associated Types
Methods from :: MemoryCpuWith i -> Rep (MemoryCpuWith i) x # to :: Rep (MemoryCpuWith i) x -> MemoryCpuWith i # | |||||
Generic (Root a) | |||||
Defined in Numeric.RootFinding Associated Types
| |||||
Generic (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
Generic (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
Generic (PosState s) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
Generic (OAuth2Flow p) | |||||
Defined in Data.OpenApi.Internal Associated Types
| |||||
Generic (CodecConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from :: CodecConfig (DualBlock m a) -> Rep (CodecConfig (DualBlock m a)) x # to :: Rep (CodecConfig (DualBlock m a)) x -> CodecConfig (DualBlock m a) # | |||||
Generic (Header ByronBlock) | |||||
Defined in Ouroboros.Consensus.Byron.Ledger.Block Associated Types
Methods from :: Header ByronBlock -> Rep (Header ByronBlock) x # to :: Rep (Header ByronBlock) x -> Header ByronBlock # | |||||
Generic (Header (ShelleyBlock proto era)) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Block Associated Types
Methods from :: Header (ShelleyBlock proto era) -> Rep (Header (ShelleyBlock proto era)) x # to :: Rep (Header (ShelleyBlock proto era)) x -> Header (ShelleyBlock proto era) # | |||||
Generic (StorageConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from :: StorageConfig (DualBlock m a) -> Rep (StorageConfig (DualBlock m a)) x # to :: Rep (StorageConfig (DualBlock m a)) x -> StorageConfig (DualBlock m a) # | |||||
Generic (RealPoint blk) | |||||
Defined in Ouroboros.Consensus.Block.RealPoint Associated Types
| |||||
Generic (SelectViewTentativeState proto) | |||||
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining Associated Types
Methods from :: SelectViewTentativeState proto -> Rep (SelectViewTentativeState proto) x # to :: Rep (SelectViewTentativeState proto) x -> SelectViewTentativeState proto # | |||||
Generic (CheckpointsMap blk) | |||||
Defined in Ouroboros.Consensus.Config Associated Types
Methods from :: CheckpointsMap blk -> Rep (CheckpointsMap blk) x # to :: Rep (CheckpointsMap blk) x -> CheckpointsMap blk # | |||||
Generic (TopLevelConfig blk) | |||||
Defined in Ouroboros.Consensus.Config Associated Types
Methods from :: TopLevelConfig blk -> Rep (TopLevelConfig blk) x # to :: Rep (TopLevelConfig blk) x -> TopLevelConfig blk # | |||||
Generic (HardForkLedgerConfig xs) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Associated Types
Methods from :: HardForkLedgerConfig xs -> Rep (HardForkLedgerConfig xs) x # to :: Rep (HardForkLedgerConfig xs) x -> HardForkLedgerConfig xs # | |||||
Generic (SingleEraInfo blk) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Info Associated Types
Methods from :: SingleEraInfo blk -> Rep (SingleEraInfo blk) x # to :: Rep (SingleEraInfo blk) x -> SingleEraInfo blk # | |||||
Generic (HardForkEnvelopeErr xs) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Associated Types
Methods from :: HardForkEnvelopeErr xs -> Rep (HardForkEnvelopeErr xs) x # to :: Rep (HardForkEnvelopeErr xs) x -> HardForkEnvelopeErr xs # | |||||
Generic (HardForkLedgerError xs) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Associated Types
Methods from :: HardForkLedgerError xs -> Rep (HardForkLedgerError xs) x # to :: Rep (HardForkLedgerError xs) x -> HardForkLedgerError xs # | |||||
Generic (HardForkApplyTxErr xs) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from :: HardForkApplyTxErr xs -> Rep (HardForkApplyTxErr xs) x # to :: Rep (HardForkApplyTxErr xs) x -> HardForkApplyTxErr xs # | |||||
Generic (HardForkValidationErr xs) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol Associated Types
Methods from :: HardForkValidationErr xs -> Rep (HardForkValidationErr xs) x # to :: Rep (HardForkValidationErr xs) x -> HardForkValidationErr xs # | |||||
Generic (HeaderStateHistory blk) | |||||
Defined in Ouroboros.Consensus.HeaderStateHistory Associated Types
Methods from :: HeaderStateHistory blk -> Rep (HeaderStateHistory blk) x # to :: Rep (HeaderStateHistory blk) x -> HeaderStateHistory blk # | |||||
Generic (HeaderStateWithTime blk) | |||||
Defined in Ouroboros.Consensus.HeaderStateHistory Associated Types
Methods from :: HeaderStateWithTime blk -> Rep (HeaderStateWithTime blk) x # to :: Rep (HeaderStateWithTime blk) x -> HeaderStateWithTime blk # | |||||
Generic (AnnTip blk) | |||||
Defined in Ouroboros.Consensus.HeaderValidation Associated Types
| |||||
Generic (HeaderEnvelopeError blk) | |||||
Defined in Ouroboros.Consensus.HeaderValidation Associated Types
Methods from :: HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x # to :: Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk # | |||||
Generic (HeaderError blk) | |||||
Defined in Ouroboros.Consensus.HeaderValidation Associated Types
Methods from :: HeaderError blk -> Rep (HeaderError blk) x # to :: Rep (HeaderError blk) x -> HeaderError blk # | |||||
Generic (HeaderState blk) | |||||
Defined in Ouroboros.Consensus.HeaderValidation Associated Types
Methods from :: HeaderState blk -> Rep (HeaderState blk) x # to :: Rep (HeaderState blk) x -> HeaderState blk # | |||||
Generic (TipInfoIsEBB blk) | |||||
Defined in Ouroboros.Consensus.HeaderValidation Associated Types
Methods from :: TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x # to :: Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk # | |||||
Generic (ExtLedgerCfg blk) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Associated Types
Methods from :: ExtLedgerCfg blk -> Rep (ExtLedgerCfg blk) x # to :: Rep (ExtLedgerCfg blk) x -> ExtLedgerCfg blk # | |||||
Generic (ExtLedgerState blk) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Associated Types
Methods from :: ExtLedgerState blk -> Rep (ExtLedgerState blk) x # to :: Rep (ExtLedgerState blk) x -> ExtLedgerState blk # | |||||
Generic (ExtValidationError blk) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Associated Types
Methods from :: ExtValidationError blk -> Rep (ExtValidationError blk) x # to :: Rep (ExtValidationError blk) x -> ExtValidationError blk # | |||||
Generic (InternalState blk) | |||||
Defined in Ouroboros.Consensus.Mempool.Impl.Common Associated Types
Methods from :: InternalState blk -> Rep (InternalState blk) x # to :: Rep (InternalState blk) x -> InternalState blk # | |||||
Generic (Idling m) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic (KnownIntersectionState blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic (LoPBucket m) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic (UnknownIntersectionState blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
| |||||
Generic (Instruction blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.Jumping Associated Types
Methods from :: Instruction blk -> Rep (Instruction blk) x # to :: Rep (Instruction blk) x -> Instruction blk # | |||||
Generic (JumpInstruction blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.Jumping Associated Types
Methods from :: JumpInstruction blk -> Rep (JumpInstruction blk) x # to :: Rep (JumpInstruction blk) x -> JumpInstruction blk # | |||||
Generic (JumpResult blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.Jumping Associated Types
Methods from :: JumpResult blk -> Rep (JumpResult blk) x # to :: Rep (JumpResult blk) x -> JumpResult blk # | |||||
Generic (ChainSyncJumpingJumperState blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ChainSyncJumpingJumperState blk -> Rep (ChainSyncJumpingJumperState blk) x # to :: Rep (ChainSyncJumpingJumperState blk) x -> ChainSyncJumpingJumperState blk # | |||||
Generic (ChainSyncState blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ChainSyncState blk -> Rep (ChainSyncState blk) x # to :: Rep (ChainSyncState blk) x -> ChainSyncState blk # | |||||
Generic (DynamoInitState blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: DynamoInitState blk -> Rep (DynamoInitState blk) x # to :: Rep (DynamoInitState blk) x -> DynamoInitState blk # | |||||
Generic (JumpInfo blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
| |||||
Generic (ConsensusConfig (HardForkProtocol xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Associated Types
Methods from :: ConsensusConfig (HardForkProtocol xs) -> Rep (ConsensusConfig (HardForkProtocol xs)) x # to :: Rep (ConsensusConfig (HardForkProtocol xs)) x -> ConsensusConfig (HardForkProtocol xs) # | |||||
Generic (ConsensusConfig (Bft c)) | |||||
Defined in Ouroboros.Consensus.Protocol.BFT Associated Types
Methods from :: ConsensusConfig (Bft c) -> Rep (ConsensusConfig (Bft c)) x # to :: Rep (ConsensusConfig (Bft c)) x -> ConsensusConfig (Bft c) # | |||||
Generic (ConsensusConfig (ModChainSel p s)) | |||||
Defined in Ouroboros.Consensus.Protocol.ModChainSel Associated Types
Methods from :: ConsensusConfig (ModChainSel p s) -> Rep (ConsensusConfig (ModChainSel p s)) x # to :: Rep (ConsensusConfig (ModChainSel p s)) x -> ConsensusConfig (ModChainSel p s) # | |||||
Generic (ConsensusConfig (PBft c)) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: ConsensusConfig (PBft c) -> Rep (ConsensusConfig (PBft c)) x # to :: Rep (ConsensusConfig (PBft c)) x -> ConsensusConfig (PBft c) # | |||||
Generic (ConsensusConfig (Praos c)) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: ConsensusConfig (Praos c) -> Rep (ConsensusConfig (Praos c)) x # to :: Rep (ConsensusConfig (Praos c)) x -> ConsensusConfig (Praos c) # | |||||
Generic (ConsensusConfig (TPraos c)) | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
Methods from :: ConsensusConfig (TPraos c) -> Rep (ConsensusConfig (TPraos c)) x # to :: Rep (ConsensusConfig (TPraos c)) x -> ConsensusConfig (TPraos c) # | |||||
Generic (PBftCanBeLeader c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftCanBeLeader c -> Rep (PBftCanBeLeader c) x # to :: Rep (PBftCanBeLeader c) x -> PBftCanBeLeader c # | |||||
Generic (PBftCannotForge c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftCannotForge c -> Rep (PBftCannotForge c) x # to :: Rep (PBftCannotForge c) x -> PBftCannotForge c # | |||||
Generic (PBftIsLeader c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftIsLeader c -> Rep (PBftIsLeader c) x # to :: Rep (PBftIsLeader c) x -> PBftIsLeader c # | |||||
Generic (PBftLedgerView c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftLedgerView c -> Rep (PBftLedgerView c) x # to :: Rep (PBftLedgerView c) x -> PBftLedgerView c # | |||||
Generic (PBftValidationErr c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftValidationErr c -> Rep (PBftValidationErr c) x # to :: Rep (PBftValidationErr c) x -> PBftValidationErr c # | |||||
Generic (PBftSigner c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT.State Associated Types
| |||||
Generic (PBftState c) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT.State Associated Types
| |||||
Generic (LoE a) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.API Associated Types
| |||||
Generic (InImmutableDBEnd blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Iterator Associated Types
| |||||
Generic (FollowerRollState blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: FollowerRollState blk -> Rep (FollowerRollState blk) x # to :: Rep (FollowerRollState blk) x -> FollowerRollState blk # | |||||
Generic (InvalidBlockInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x # to :: Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk # | |||||
Generic (SelectionChangedInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: SelectionChangedInfo blk -> Rep (SelectionChangedInfo blk) x # to :: Rep (SelectionChangedInfo blk) x -> SelectionChangedInfo blk # | |||||
Generic (TraceAddBlockEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x # to :: Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk # | |||||
Generic (TraceChainSelStarvationEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceChainSelStarvationEvent blk -> Rep (TraceChainSelStarvationEvent blk) x # to :: Rep (TraceChainSelStarvationEvent blk) x -> TraceChainSelStarvationEvent blk # | |||||
Generic (TraceCopyToImmutableDBEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceCopyToImmutableDBEvent blk -> Rep (TraceCopyToImmutableDBEvent blk) x # to :: Rep (TraceCopyToImmutableDBEvent blk) x -> TraceCopyToImmutableDBEvent blk # | |||||
Generic (TraceEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceEvent blk -> Rep (TraceEvent blk) x # to :: Rep (TraceEvent blk) x -> TraceEvent blk # | |||||
Generic (TraceFollowerEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x # to :: Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk # | |||||
Generic (TraceGCEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceGCEvent blk -> Rep (TraceGCEvent blk) x # to :: Rep (TraceGCEvent blk) x -> TraceGCEvent blk # | |||||
Generic (TraceInitChainSelEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x # to :: Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk # | |||||
Generic (TraceIteratorEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x # to :: Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk # | |||||
Generic (TraceOpenEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x # to :: Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk # | |||||
Generic (TraceValidationEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x # to :: Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk # | |||||
Generic (StreamFrom blk) | |||||
Defined in Ouroboros.Consensus.Storage.Common Associated Types
Methods from :: StreamFrom blk -> Rep (StreamFrom blk) x # to :: Rep (StreamFrom blk) x -> StreamFrom blk # | |||||
Generic (StreamTo blk) | |||||
Defined in Ouroboros.Consensus.Storage.Common Associated Types
| |||||
Generic (ImmutableDBError blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.API Associated Types
Methods from :: ImmutableDBError blk -> Rep (ImmutableDBError blk) x # to :: Rep (ImmutableDBError blk) x -> ImmutableDBError blk # | |||||
Generic (IteratorResult b) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.API Associated Types
Methods from :: IteratorResult b -> Rep (IteratorResult b) x # to :: Rep (IteratorResult b) x -> IteratorResult b # | |||||
Generic (MissingBlock blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.API Associated Types
Methods from :: MissingBlock blk -> Rep (MissingBlock blk) x # to :: Rep (MissingBlock blk) x -> MissingBlock blk # | |||||
Generic (Tip blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.API Associated Types
| |||||
Generic (Cached blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache Associated Types
| |||||
Generic (CurrentChunkInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache Associated Types
| |||||
Generic (PastChunkInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache Associated Types
| |||||
Generic (Entry blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary Associated Types
| |||||
Generic (TraceEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
Methods from :: TraceEvent blk -> Rep (TraceEvent blk) x # to :: Rep (TraceEvent blk) x -> TraceEvent blk # | |||||
Generic (WithBlockSize a) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
Methods from :: WithBlockSize a -> Rep (WithBlockSize a) x # to :: Rep (WithBlockSize a) x -> WithBlockSize a # | |||||
Generic (InitLog blk) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Init Associated Types
| |||||
Generic (TraceReplayEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Init Associated Types
Methods from :: TraceReplayEvent blk -> Rep (TraceReplayEvent blk) x # to :: Rep (TraceReplayEvent blk) x -> TraceReplayEvent blk # | |||||
Generic (Checkpoint l) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB Associated Types
| |||||
Generic (LedgerDB l) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB Associated Types
| |||||
Generic (SnapshotFailure blk) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Snapshots Associated Types
Methods from :: SnapshotFailure blk -> Rep (SnapshotFailure blk) x # to :: Rep (SnapshotFailure blk) x -> SnapshotFailure blk # | |||||
Generic (TraceSnapshotEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Snapshots Associated Types
Methods from :: TraceSnapshotEvent blk -> Rep (TraceSnapshotEvent blk) x # to :: Rep (TraceSnapshotEvent blk) x -> TraceSnapshotEvent blk # | |||||
Generic (UpdateLedgerDbTraceEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.Update Associated Types
Methods from :: UpdateLedgerDbTraceEvent blk -> Rep (UpdateLedgerDbTraceEvent blk) x # to :: Rep (UpdateLedgerDbTraceEvent blk) x -> UpdateLedgerDbTraceEvent blk # | |||||
Generic (BlockInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.API Associated Types
| |||||
Generic (FileInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.FileInfo Associated Types
| |||||
Generic (Index blk) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Index Associated Types
| |||||
Generic (InternalBlockInfo blk) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types Associated Types
Methods from :: InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x # to :: Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk # | |||||
Generic (TraceEvent blk) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types Associated Types
Methods from :: TraceEvent blk -> Rep (TraceEvent blk) x # to :: Rep (TraceEvent blk) x -> TraceEvent blk # | |||||
Generic (Flag name) | |||||
Defined in Ouroboros.Consensus.Util Associated Types
| |||||
Generic (Fuse m) | |||||
Defined in Ouroboros.Consensus.Util Associated Types
| |||||
Generic (Config m) | |||||
Defined in Ouroboros.Consensus.Util.LeakyBucket Associated Types
| |||||
Generic (State m) | |||||
Defined in Ouroboros.Consensus.Util.LeakyBucket Associated Types
| |||||
Generic (WithFingerprint a) | |||||
Defined in Ouroboros.Consensus.Util.STM Associated Types
Methods from :: WithFingerprint a -> Rep (WithFingerprint a) x # to :: Rep (WithFingerprint a) x -> WithFingerprint a # | |||||
Generic (ShelleyLedgerConfig era) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger Associated Types
Methods from :: ShelleyLedgerConfig era -> Rep (ShelleyLedgerConfig era) x # to :: Rep (ShelleyLedgerConfig era) x -> ShelleyLedgerConfig era # | |||||
Generic (ShelleyPartialLedgerConfig era) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger Associated Types
Methods from :: ShelleyPartialLedgerConfig era -> Rep (ShelleyPartialLedgerConfig era) x # to :: Rep (ShelleyPartialLedgerConfig era) x -> ShelleyPartialLedgerConfig era # | |||||
Generic (IndividualPoolStake c) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Query.Types Associated Types
Methods from :: IndividualPoolStake c -> Rep (IndividualPoolStake c) x # to :: Rep (IndividualPoolStake c) x -> IndividualPoolStake c # | |||||
Generic (PoolDistr c) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Query.Types Associated Types
| |||||
Generic (HotIdentity c) | |||||
Defined in Ouroboros.Consensus.Shelley.Node.DiffusionPipelining Associated Types
Methods from :: HotIdentity c -> Rep (HotIdentity c) x # to :: Rep (HotIdentity c) x -> HotIdentity c # | |||||
Generic (ShelleyTentativeHeaderState proto) | |||||
Defined in Ouroboros.Consensus.Shelley.Node.DiffusionPipelining Associated Types
Methods from :: ShelleyTentativeHeaderState proto -> Rep (ShelleyTentativeHeaderState proto) x # to :: Rep (ShelleyTentativeHeaderState proto) x -> ShelleyTentativeHeaderState proto # | |||||
Generic (LoEAndGDDConfig a) | |||||
Defined in Ouroboros.Consensus.Node.Genesis Associated Types
Methods from :: LoEAndGDDConfig a -> Rep (LoEAndGDDConfig a) x # to :: Rep (LoEAndGDDConfig a) x -> LoEAndGDDConfig a # | |||||
Generic (KESKey c) | |||||
Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey Associated Types
| |||||
Generic (KESState c) | |||||
Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey Associated Types
| |||||
Generic (PraosCannotForge c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: PraosCannotForge c -> Rep (PraosCannotForge c) x # to :: Rep (PraosCannotForge c) x -> PraosCannotForge c # | |||||
Generic (PraosIsLeader c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: PraosIsLeader c -> Rep (PraosIsLeader c) x # to :: Rep (PraosIsLeader c) x -> PraosIsLeader c # | |||||
Generic (PraosToSign c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: PraosToSign c -> Rep (PraosToSign c) x # to :: Rep (PraosToSign c) x -> PraosToSign c # | |||||
Generic (PraosValidationErr c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: PraosValidationErr c -> Rep (PraosValidationErr c) x # to :: Rep (PraosValidationErr c) x -> PraosValidationErr c # | |||||
Generic (PraosCanBeLeader c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Common Associated Types
Methods from :: PraosCanBeLeader c -> Rep (PraosCanBeLeader c) x # to :: Rep (PraosCanBeLeader c) x -> PraosCanBeLeader c # | |||||
Generic (PraosChainSelectView c) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Common Associated Types
Methods from :: PraosChainSelectView c -> Rep (PraosChainSelectView c) x # to :: Rep (PraosChainSelectView c) x -> PraosChainSelectView c # | |||||
Generic (Header crypto) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Header Associated Types
| |||||
Generic (HeaderBody crypto) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Header Associated Types
Methods from :: HeaderBody crypto -> Rep (HeaderBody crypto) x # to :: Rep (HeaderBody crypto) x -> HeaderBody crypto # | |||||
Generic (HeaderRaw crypto) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos.Header Associated Types
| |||||
Generic (TPraosCannotForge c) | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
Methods from :: TPraosCannotForge c -> Rep (TPraosCannotForge c) x # to :: Rep (TPraosCannotForge c) x -> TPraosCannotForge c # | |||||
Generic (TPraosIsLeader c) | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
Methods from :: TPraosIsLeader c -> Rep (TPraosIsLeader c) x # to :: Rep (TPraosIsLeader c) x -> TPraosIsLeader c # | |||||
Generic (TPraosToSign c) | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
Methods from :: TPraosToSign c -> Rep (TPraosToSign c) x # to :: Rep (TPraosToSign c) x -> TPraosToSign c # | |||||
Generic (PeerMetricsState p) | |||||
Defined in Ouroboros.Network.PeerSelection.PeerMetric Associated Types
| |||||
Generic (Anchor block) | |||||
Defined in Ouroboros.Network.AnchoredFragment Associated Types
| |||||
Generic (ConnectionId addr) | |||||
Defined in Ouroboros.Network.ConnectionId Associated Types
Methods from :: ConnectionId addr -> Rep (ConnectionId addr) x # to :: Rep (ConnectionId addr) x -> ConnectionId addr # | |||||
Generic (RefuseReason vNumber) | |||||
Defined in Ouroboros.Network.Protocol.Handshake.Type Associated Types
Methods from :: RefuseReason vNumber -> Rep (RefuseReason vNumber) x # to :: Rep (RefuseReason vNumber) x -> RefuseReason vNumber # | |||||
Generic (TestAddress addr) | |||||
Defined in Ouroboros.Network.Snocket Associated Types
Methods from :: TestAddress addr -> Rep (TestAddress addr) x # to :: Rep (TestAddress addr) x -> TestAddress addr # | |||||
Generic (ChainRange point) | |||||
Defined in Ouroboros.Network.Protocol.BlockFetch.Type Associated Types
Methods from :: ChainRange point -> Rep (ChainRange point) x # to :: Rep (ChainRange point) x -> ChainRange point # | |||||
Generic (Target point) | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Associated Types
| |||||
Generic (SizeAndCapacity a) | |||||
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type Associated Types
Methods from :: SizeAndCapacity a -> Rep (SizeAndCapacity a) x # to :: Rep (SizeAndCapacity a) x -> SizeAndCapacity a # | |||||
Generic (BuiltinSemanticsVariant DefaultFun) | |||||
Defined in PlutusCore.Default.Builtins Associated Types
Methods from :: BuiltinSemanticsVariant DefaultFun -> Rep (BuiltinSemanticsVariant DefaultFun) x # to :: Rep (BuiltinSemanticsVariant DefaultFun) x -> BuiltinSemanticsVariant DefaultFun # | |||||
Generic (Kind ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (Normalized a) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (LR a) | |||||
Defined in PlutusCore.Eq Associated Types
| |||||
Generic (RL a) | |||||
Defined in PlutusCore.Eq Associated Types
| |||||
Generic (ExpectedShapeOr a) | |||||
Defined in PlutusCore.Error Associated Types
Methods from :: ExpectedShapeOr a -> Rep (ExpectedShapeOr a) x # to :: Rep (ExpectedShapeOr a) x -> ExpectedShapeOr a # | |||||
Generic (UniqueError ann) | |||||
Defined in PlutusCore.Error Associated Types
Methods from :: UniqueError ann -> Rep (UniqueError ann) x # to :: Rep (UniqueError ann) x -> UniqueError ann # | |||||
Generic (BuiltinCostModelBase f) | |||||
Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel Associated Types
Methods from :: BuiltinCostModelBase f -> Rep (BuiltinCostModelBase f) x # to :: Rep (BuiltinCostModelBase f) x -> BuiltinCostModelBase f # | |||||
Generic (CostingFun model) | |||||
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core Associated Types
Methods from :: CostingFun model -> Rep (CostingFun model) x # to :: Rep (CostingFun model) x -> CostingFun model # | |||||
Generic (MachineError fun) | |||||
Defined in PlutusCore.Evaluation.Machine.Exception Associated Types
Methods from :: MachineError fun -> Rep (MachineError fun) x # to :: Rep (MachineError fun) x -> MachineError fun # | |||||
Generic (EvaluationResult a) | |||||
Defined in PlutusCore.Evaluation.Result Associated Types
Methods from :: EvaluationResult a -> Rep (EvaluationResult a) x # to :: Rep (EvaluationResult a) x -> EvaluationResult a # | |||||
Generic (CekMachineCostsBase f) | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts Associated Types
Methods from :: CekMachineCostsBase f -> Rep (CekMachineCostsBase f) x # to :: Rep (CekMachineCostsBase f) x -> CekMachineCostsBase f # | |||||
Generic (CekExTally fun) | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode Associated Types
Methods from :: CekExTally fun -> Rep (CekExTally fun) x # to :: Rep (CekExTally fun) x -> CekExTally fun # | |||||
Generic (TallyingSt fun) | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode Associated Types
Methods from :: TallyingSt fun -> Rep (TallyingSt fun) x # to :: Rep (TallyingSt fun) x -> TallyingSt fun # | |||||
Generic (ExBudgetCategory fun) | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal Associated Types
Methods from :: ExBudgetCategory fun -> Rep (ExBudgetCategory fun) x # to :: Rep (ExBudgetCategory fun) x -> ExBudgetCategory fun # | |||||
Generic (Provenance a) | |||||
Defined in PlutusIR.Compiler.Provenance Associated Types
| |||||
Generic (Extended a) | |||||
Defined in PlutusLedgerApi.V1.Data.Interval Associated Types
| |||||
Generic (Interval a) | |||||
Defined in PlutusLedgerApi.V1.Data.Interval Associated Types
| |||||
Generic (LowerBound a) | |||||
Defined in PlutusLedgerApi.V1.Data.Interval Associated Types
| |||||
Generic (UpperBound a) | |||||
Defined in PlutusLedgerApi.V1.Data.Interval Associated Types
| |||||
Generic (Extended a) | |||||
Defined in PlutusLedgerApi.V1.Interval Associated Types
| |||||
Generic (Interval a) | |||||
Defined in PlutusLedgerApi.V1.Interval Associated Types
| |||||
Generic (LowerBound a) | |||||
Defined in PlutusLedgerApi.V1.Interval Associated Types
| |||||
Generic (UpperBound a) | |||||
Defined in PlutusLedgerApi.V1.Interval Associated Types
| |||||
Generic (ConstructorSchema referencedTypes) | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
Methods from :: ConstructorSchema referencedTypes -> Rep (ConstructorSchema referencedTypes) x # to :: Rep (ConstructorSchema referencedTypes) x -> ConstructorSchema referencedTypes # | |||||
Generic (ListSchema referencedTypes) | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
Methods from :: ListSchema referencedTypes -> Rep (ListSchema referencedTypes) x # to :: Rep (ListSchema referencedTypes) x -> ListSchema referencedTypes # | |||||
Generic (MapSchema referencedTypes) | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
| |||||
Generic (PairSchema referencedTypes) | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
Methods from :: PairSchema referencedTypes -> Rep (PairSchema referencedTypes) x # to :: Rep (PairSchema referencedTypes) x -> PairSchema referencedTypes # | |||||
Generic (Schema referencedTypes) | |||||
Defined in PlutusTx.Blueprint.Schema Associated Types
| |||||
Generic (Doc a) | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
Generic (CommaSeparated a) | |||||
Defined in Text.Pretty.Simple.Internal.Expr Associated Types
Methods from :: CommaSeparated a -> Rep (CommaSeparated a) x # to :: Rep (CommaSeparated a) x -> CommaSeparated a # | |||||
Generic (Doc ann) | |||||
Defined in Prettyprinter.Internal Associated Types
| |||||
Generic (SimpleDocStream ann) | |||||
Defined in Prettyprinter.Internal Associated Types
Methods from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x # to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann # | |||||
Generic (SimpleDocTree ann) | |||||
Defined in Prettyprinter.Render.Util.SimpleDocTree Associated Types
Methods from :: SimpleDocTree ann -> Rep (SimpleDocTree ann) x # to :: Rep (SimpleDocTree ann) x -> SimpleDocTree ann # | |||||
Generic (Poisonable st) | |||||
Defined in Control.RAWLock Associated Types
| |||||
Generic (RegistryState m) | |||||
Defined in Control.ResourceRegistry Associated Types
| |||||
Generic (Resource m) | |||||
Defined in Control.ResourceRegistry Associated Types
| |||||
Generic (ResourceKey m) | |||||
Defined in Control.ResourceRegistry Associated Types
Methods from :: ResourceKey m -> Rep (ResourceKey m) x # to :: Rep (ResourceKey m) x -> ResourceKey m # | |||||
Generic (ResourceRegistry m) | |||||
Defined in Control.ResourceRegistry Associated Types
Methods from :: ResourceRegistry m -> Rep (ResourceRegistry m) x # to :: Rep (ResourceRegistry m) x -> ResourceRegistry m # | |||||
Generic (Dense currency) | |||||
Defined in Money.Internal Associated Types
| |||||
Generic (ClientM a) | |||||
Generic (ClientM a) | |||||
Defined in Servant.Client.Internal.HttpClient.Streaming Associated Types
| |||||
Generic (ResponseF a) | |||||
Defined in Servant.Client.Core.Response Associated Types
| |||||
Generic (I a) | |||||
Defined in Data.SOP.BasicFunctors Associated Types
| |||||
Generic (LinearTransform d) | |||||
Defined in Statistics.Distribution.Transform Associated Types
Methods from :: LinearTransform d -> Rep (LinearTransform d) x # to :: Rep (LinearTransform d) x -> LinearTransform d # | |||||
Generic (Maybe a) | |||||
Defined in Data.Strict.Maybe Associated Types
| |||||
Generic (ParamSchema t) | |||||
Defined in Data.Swagger.Internal Associated Types
Methods from :: ParamSchema t -> Rep (ParamSchema t) x # to :: Rep (ParamSchema t) x -> ParamSchema t # | |||||
Generic (TyVarBndr flag) | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
Generic (Window a) | |||||
Defined in System.Console.Terminal.Common Associated Types
| |||||
Generic (Doc a) | |||||
Defined in Text.PrettyPrint.Annotated.WL Associated Types
| |||||
Generic (SimpleDoc a) | |||||
Defined in Text.PrettyPrint.Annotated.WL Associated Types
| |||||
Generic (Maybe a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Solo a) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic [a] | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple2 a b) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (Graph e a) | |||||
Defined in Algebra.Graph.Labelled Associated Types
| |||||
Generic (AdjacencyMap e a) | |||||
Defined in Algebra.Graph.Labelled.AdjacencyMap Associated Types
Methods from :: AdjacencyMap e a -> Rep (AdjacencyMap e a) x # to :: Rep (AdjacencyMap e a) x -> AdjacencyMap e a # | |||||
Generic (Container b a) | |||||
Defined in Barbies.Internal.Containers Associated Types
| |||||
Generic (ErrorContainer b e) | |||||
Defined in Barbies.Internal.Containers Associated Types
Methods from :: ErrorContainer b e -> Rep (ErrorContainer b e) x # to :: Rep (ErrorContainer b e) x -> ErrorContainer b e # | |||||
Generic (Unit f) | |||||
Defined in Barbies.Internal.Trivial | |||||
Generic (Void f) | |||||
Defined in Barbies.Internal.Trivial | |||||
Generic (WrappedMonad m a) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedMonad m a -> Rep (WrappedMonad m a) x # to :: Rep (WrappedMonad m a) x -> WrappedMonad m a # | |||||
Generic (Arg a b) | |||||
Defined in Data.Semigroup Associated Types
| |||||
Generic (ListN n a) | |||||
Defined in Basement.Sized.List Associated Types
| |||||
Generic (Bimap a b) | |||||
Defined in Data.Bimap Associated Types
| |||||
Generic (Index derivationType depth) | |||||
Defined in Cardano.Address.Derivation Associated Types
| |||||
Generic (Byron depth key) | |||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||
Generic (Icarus depth key) | |||||
Defined in Cardano.Address.Style.Icarus Associated Types
| |||||
Generic (Shared depth key) | |||||
Generic (Shelley depth key) | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
Generic (SignedDSIGN v a) | |||||
Defined in Cardano.Crypto.DSIGN.Class Associated Types
Methods from :: SignedDSIGN v a -> Rep (SignedDSIGN v a) x # to :: Rep (SignedDSIGN v a) x -> SignedDSIGN v a # | |||||
Generic (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class Associated Types
| |||||
Generic (SignedKES v a) | |||||
Defined in Cardano.Crypto.KES.Class Associated Types
| |||||
Generic (CertifiedVRF v a) | |||||
Defined in Cardano.Crypto.VRF.Class Associated Types
Methods from :: CertifiedVRF v a -> Rep (CertifiedVRF v a) x # to :: Rep (CertifiedVRF v a) x -> CertifiedVRF v a # | |||||
Generic (AbstractHash algo a) | |||||
Defined in Cardano.Crypto.Hashing Associated Types
Methods from :: AbstractHash algo a -> Rep (AbstractHash algo a) x # to :: Rep (AbstractHash algo a) x -> AbstractHash algo a # | |||||
Generic (ListMap k v) | |||||
Defined in Data.ListMap Associated Types
| |||||
Generic (OMap k v) | |||||
Defined in Data.OMap.Strict Associated Types
| |||||
Generic (Timelock era) | |||||
Defined in Cardano.Ledger.Allegra.Scripts Associated Types
| |||||
Generic (TimelockRaw era) | |||||
Defined in Cardano.Ledger.Allegra.Scripts Associated Types
Methods from :: TimelockRaw era -> Rep (TimelockRaw era) x # to :: Rep (TimelockRaw era) x -> TimelockRaw era # | |||||
Generic (AllegraTxBodyRaw ma era) | |||||
Defined in Cardano.Ledger.Allegra.TxBody.Internal Associated Types
Methods from :: AllegraTxBodyRaw ma era -> Rep (AllegraTxBodyRaw ma era) x # to :: Rep (AllegraTxBodyRaw ma era) x -> AllegraTxBodyRaw ma era # | |||||
Generic (AlonzoPParams f era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Associated Types
Methods from :: AlonzoPParams f era -> Rep (AlonzoPParams f era) x # to :: Rep (AlonzoPParams f era) x -> AlonzoPParams f era # | |||||
Generic (AlonzoContextError era) | |||||
Defined in Cardano.Ledger.Alonzo.Plutus.TxInfo Associated Types
Methods from :: AlonzoContextError era -> Rep (AlonzoContextError era) x # to :: Rep (AlonzoContextError era) x -> AlonzoContextError era # | |||||
Generic (AlonzoPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods from :: AlonzoPlutusPurpose f era -> Rep (AlonzoPlutusPurpose f era) x # to :: Rep (AlonzoPlutusPurpose f era) x -> AlonzoPlutusPurpose f era # | |||||
Generic it => Generic (AsItem ix it) | |||||
Generic ix => Generic (AsIx ix it) | |||||
Generic (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
| |||||
Generic (BabbagePParams f era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Associated Types
Methods from :: BabbagePParams f era -> Rep (BabbagePParams f era) x # to :: Rep (BabbagePParams f era) x -> BabbagePParams f era # | |||||
Generic (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Associated Types
| |||||
Generic (GovPurposeId p era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovPurposeId p era -> Rep (GovPurposeId p era) x # to :: Rep (GovPurposeId p era) x -> GovPurposeId p era # | |||||
Generic (GovRelation f era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovRelation f era -> Rep (GovRelation f era) x # to :: Rep (GovRelation f era) x -> GovRelation f era # | |||||
Generic (ConwayPParams f era) | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: ConwayPParams f era -> Rep (ConwayPParams f era) x # to :: Rep (ConwayPParams f era) x -> ConwayPParams f era # | |||||
Generic (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Associated Types
Methods from :: ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x # to :: Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era # | |||||
Generic (BoundedRatio b a) | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic (Mismatch r a) | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Generic (Block h era) | |||||
Defined in Cardano.Ledger.Block Associated Types
| |||||
Generic (ShelleyPParams f era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Associated Types
Methods from :: ShelleyPParams f era -> Rep (ShelleyPParams f era) x # to :: Rep (ShelleyPParams f era) x -> ShelleyPParams f era # | |||||
Generic (SearchResult v a) | |||||
Defined in Data.FingerTree.Strict Associated Types
Methods from :: SearchResult v a -> Rep (SearchResult v a) x # to :: Rep (SearchResult v a) x -> SearchResult v a # | |||||
Generic (FingerTree v a) | |||||
Defined in Data.FingerTree Associated Types
Methods from :: FingerTree v a -> Rep (FingerTree v a) x # to :: Rep (FingerTree v a) x -> FingerTree v a # | |||||
Generic (Node v a) | |||||
Defined in Data.FingerTree Associated Types
| |||||
Generic (SearchResult v a) | |||||
Defined in Data.FingerTree Associated Types
Methods from :: SearchResult v a -> Rep (SearchResult v a) x # to :: Rep (SearchResult v a) x -> SearchResult v a # | |||||
Generic (ViewL s a) | |||||
Defined in Data.FingerTree Associated Types
| |||||
Generic (ViewR s a) | |||||
Defined in Data.FingerTree Associated Types
| |||||
Generic (Tuple2 a b) | |||||
Defined in Foundation.Tuple Associated Types
| |||||
Generic (Cofree f a) | |||||
Defined in Control.Comonad.Cofree Associated Types
| |||||
Generic (Free f a) | |||||
Defined in Control.Monad.Free Associated Types
| |||||
Generic (Either a b) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Proxy t) | |||||
Defined in GHC.Internal.Generics | |||||
Generic (U1 p) | |||||
Defined in GHC.Internal.Generics | |||||
Generic (V1 p) | |||||
Generic (IPRTable k a) | |||||
Defined in Data.IP.RouteTable.Internal Associated Types
| |||||
Generic (ListT m a) | |||||
Defined in ListT Associated Types
| |||||
Generic (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseError s e -> Rep (ParseError s e) x # to :: Rep (ParseError s e) x -> ParseError s e # | |||||
Generic (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x # to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e # | |||||
Generic (State s e) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
Generic (FirstToFinish m a) | |||||
Defined in Data.Monoid.Synchronisation Associated Types
Methods from :: FirstToFinish m a -> Rep (FirstToFinish m a) x # to :: Rep (FirstToFinish m a) x -> FirstToFinish m a # | |||||
Generic (LastToFinish m a) | |||||
Defined in Data.Monoid.Synchronisation Associated Types
Methods from :: LastToFinish m a -> Rep (LastToFinish m a) x # to :: Rep (LastToFinish m a) x -> LastToFinish m a # | |||||
Generic (LastToFinishM m a) | |||||
Defined in Data.Monoid.Synchronisation Associated Types
Methods from :: LastToFinishM m a -> Rep (LastToFinishM m a) x # to :: Rep (LastToFinishM m a) x -> LastToFinishM m a # | |||||
Generic (WithBearer peerid a) | |||||
Defined in Network.Mux.Trace Associated Types
Methods from :: WithBearer peerid a -> Rep (WithBearer peerid a) x # to :: Rep (WithBearer peerid a) x -> WithBearer peerid a # | |||||
Generic (Current f blk) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types Associated Types
| |||||
Generic (TxTicket sz tx) | |||||
Defined in Ouroboros.Consensus.Mempool.TxSeq Associated Types
| |||||
Generic (ChainSyncStateView m blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client Associated Types
Methods from :: ChainSyncStateView m blk -> Rep (ChainSyncStateView m blk) x # to :: Rep (ChainSyncStateView m blk) x -> ChainSyncStateView m blk # | |||||
Generic (Jumping m blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.Jumping Associated Types
| |||||
Generic (ChainSyncClientHandle m blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ChainSyncClientHandle m blk -> Rep (ChainSyncClientHandle m blk) x # to :: Rep (ChainSyncClientHandle m blk) x -> ChainSyncClientHandle m blk # | |||||
Generic (ChainSyncJumpingState m blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ChainSyncJumpingState m blk -> Rep (ChainSyncJumpingState m blk) x # to :: Rep (ChainSyncJumpingState m blk) x -> ChainSyncJumpingState m blk # | |||||
Generic (BftFields c toSign) | |||||
Defined in Ouroboros.Consensus.Protocol.BFT Associated Types
| |||||
Generic (PBftFields c toSign) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT Associated Types
Methods from :: PBftFields c toSign -> Rep (PBftFields c toSign) x # to :: Rep (PBftFields c toSign) x -> PBftFields c toSign # | |||||
Generic (LgrDB m blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB Associated Types
| |||||
Generic (ChainDbEnv m blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x # to :: Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk # | |||||
Generic (ChainDbState m blk) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: ChainDbState m blk -> Rep (ChainDbState m blk) x # to :: Rep (ChainDbState m blk) x -> ChainDbState m blk # | |||||
Generic (TraceChunkValidation blk validateTo) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types Associated Types
Methods from :: TraceChunkValidation blk validateTo -> Rep (TraceChunkValidation blk validateTo) x # to :: Rep (TraceChunkValidation blk validateTo) x -> TraceChunkValidation blk validateTo # | |||||
Generic (LedgerDbCfgF f l) | |||||
Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB Associated Types
Methods from :: LedgerDbCfgF f l -> Rep (LedgerDbCfgF f l) x # to :: Rep (LedgerDbCfgF f l) x -> LedgerDbCfgF f l # | |||||
Generic (InternalState blk h) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State Associated Types
Methods from :: InternalState blk h -> Rep (InternalState blk h) x # to :: Rep (InternalState blk h) x -> InternalState blk h # | |||||
Generic (OpenState blk h) | |||||
Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State Associated Types
| |||||
Generic (ShelleyTip proto era) | |||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger Associated Types
Methods from :: ShelleyTip proto era -> Rep (ShelleyTip proto era) x # to :: Rep (ShelleyTip proto era) x -> ShelleyTip proto era # | |||||
Generic (PraosFields c toSign) | |||||
Defined in Ouroboros.Consensus.Protocol.Praos Associated Types
Methods from :: PraosFields c toSign -> Rep (PraosFields c toSign) x # to :: Rep (PraosFields c toSign) x -> PraosFields c toSign # | |||||
Generic (TPraosFields c toSign) | |||||
Defined in Ouroboros.Consensus.Protocol.TPraos Associated Types
Methods from :: TPraosFields c toSign -> Rep (TPraosFields c toSign) x # to :: Rep (TPraosFields c toSign) x -> TPraosFields c toSign # | |||||
Generic (ServerState txid tx) | |||||
Defined in Ouroboros.Network.TxSubmission.Inbound Associated Types
| |||||
Generic (ChainHash b) | |||||
Defined in Ouroboros.Network.Block Associated Types
| |||||
Generic (HeaderFields b) | |||||
Defined in Ouroboros.Network.Block Associated Types
Methods from :: HeaderFields b -> Rep (HeaderFields b) x # to :: Rep (HeaderFields b) x -> HeaderFields b # | |||||
Generic (Point block) | |||||
Defined in Ouroboros.Network.Block Associated Types
| |||||
Generic (Tip b) | |||||
Defined in Ouroboros.Network.Block Associated Types
| |||||
Generic (Block slot hash) | |||||
Defined in Ouroboros.Network.Point Associated Types
| |||||
Generic (TyVarDecl tyname ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (EvaluationError structural operational) | |||||
Defined in PlutusCore.Evaluation.Error Associated Types
Methods from :: EvaluationError structural operational -> Rep (EvaluationError structural operational) x # to :: Rep (EvaluationError structural operational) x -> EvaluationError structural operational # | |||||
Generic (ErrorWithCause err cause) | |||||
Defined in PlutusCore.Evaluation.ErrorWithCause Associated Types
Methods from :: ErrorWithCause err cause -> Rep (ErrorWithCause err cause) x # to :: Rep (ErrorWithCause err cause) x -> ErrorWithCause err cause # | |||||
Generic (Def var val) | |||||
Defined in PlutusCore.MkPlc Associated Types
| |||||
Generic (UVarDecl name ann) | |||||
Defined in UntypedPlutusCore.Core.Type Associated Types
| |||||
Generic (TypeErrorExt uni ann) | |||||
Defined in PlutusIR.Error Associated Types
| |||||
Generic (Map k v) | |||||
Defined in PlutusTx.AssocMap Associated Types
| |||||
Generic (These a b) | |||||
Defined in PlutusTx.These Associated Types
| |||||
Generic (RAWLock m st) | |||||
Defined in Control.RAWLock Associated Types
| |||||
Generic (ListF a b) | |||||
Defined in Data.Functor.Base Associated Types
| |||||
Generic (NonEmptyF a b) | |||||
Defined in Data.Functor.Base Associated Types
| |||||
Generic (TreeF a b) | |||||
Defined in Data.Functor.Base Associated Types
| |||||
GoodScale scale => Generic (Discrete' currency scale) | |||||
Defined in Money.Internal Associated Types
| |||||
Generic (ExchangeRate src dst) | |||||
Defined in Money.Internal Associated Types
Methods from :: ExchangeRate src dst -> Rep (ExchangeRate src dst) x # to :: Rep (ExchangeRate src dst) x -> ExchangeRate src dst # | |||||
Generic (NoContentVerb method) | |||||
Defined in Servant.API.Verbs Associated Types
Methods from :: NoContentVerb method -> Rep (NoContentVerb method) x # to :: Rep (NoContentVerb method) x -> NoContentVerb method # | |||||
Generic (RequestF body path) | |||||
Defined in Servant.Client.Core.Request Associated Types
| |||||
Generic (Of a b) | |||||
Defined in Data.Functor.Of Associated Types
| |||||
Generic (Either a b) | |||||
Defined in Data.Strict.Either Associated Types
| |||||
Generic (These a b) | |||||
Defined in Data.Strict.These Associated Types
| |||||
Generic (Pair a b) | |||||
Defined in Data.Strict.Tuple Associated Types
| |||||
Generic (These a b) | |||||
Defined in Data.These Associated Types
| |||||
Generic (Lift f a) | |||||
Defined in Control.Applicative.Lift Associated Types
| |||||
Generic (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe Associated Types
| |||||
Generic (Validation err a) | |||||
Defined in Data.Validation Associated Types
Methods from :: Validation err a -> Rep (Validation err a) x # to :: Rep (Validation err a) x -> Validation err a # | |||||
Generic (Validation e a) | |||||
Defined in Validation Associated Types
Methods from :: Validation e a -> Rep (Validation e a) x # to :: Rep (Validation e a) x -> Validation e a # | |||||
Generic (a, b) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple3 a b c) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (WrappedArrow a b c) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x # to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c # | |||||
Generic (Fix p a) | |||||
Defined in Data.Bifunctor.Fix Associated Types
| |||||
Generic (Join p a) | |||||
Defined in Data.Bifunctor.Join Associated Types
| |||||
Generic (Tuple3 a b c) | |||||
Defined in Foundation.Tuple Associated Types
| |||||
Generic (CofreeF f a b) | |||||
Defined in Control.Comonad.Trans.Cofree Associated Types
| |||||
Generic (FreeF f a b) | |||||
Defined in Control.Monad.Trans.Free Associated Types
| |||||
Generic (Kleisli m a b) | |||||
Defined in GHC.Internal.Control.Arrow Associated Types
| |||||
Generic (Const a b) | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
Generic (Ap f a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic (Alt f a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic (Rec1 f p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec (Ptr ()) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Char p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Double p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Float p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Int p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (URec Word p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (WithBlockNo f a) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.ChainSel Associated Types
Methods from :: WithBlockNo f a -> Rep (WithBlockNo f a) x # to :: Rep (WithBlockNo f a) x -> WithBlockNo f a # | |||||
Generic (ChainSyncClientHandleCollection peer m blk) | |||||
Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.State Associated Types
Methods from :: ChainSyncClientHandleCollection peer m blk -> Rep (ChainSyncClientHandleCollection peer m blk) x # to :: Rep (ChainSyncClientHandleCollection peer m blk) x -> ChainSyncClientHandleCollection peer m blk # | |||||
Generic (IteratorState m blk b) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Iterator Associated Types
| |||||
Generic (FollowerState m blk b) | |||||
Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types Associated Types
Methods from :: FollowerState m blk b -> Rep (FollowerState m blk b) x # to :: Rep (FollowerState m blk b) x -> FollowerState m blk b # | |||||
Generic (IteratorState m blk h) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Iterator Associated Types
| |||||
Generic (IteratorStateOrExhausted m hash h) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Iterator Associated Types
| |||||
Generic (InternalState m blk h) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State Associated Types
Methods from :: InternalState m blk h -> Rep (InternalState m blk h) x # to :: Rep (InternalState m blk h) x -> InternalState m blk h # | |||||
Generic (OpenState m blk h) | |||||
Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State Associated Types
| |||||
Generic (AnchoredSeq v a b) | |||||
Defined in Ouroboros.Network.AnchoredSeq Associated Types
Methods from :: AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x # to :: Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b # | |||||
Generic (MeasuredWith v a b) | |||||
Defined in Ouroboros.Network.AnchoredSeq Associated Types
| |||||
Generic (TyDecl tyname uni ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (Type tyname uni ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (Error uni fun ann) | |||||
Defined in PlutusCore.Error Associated Types
| |||||
Generic (MachineParameters machinecosts fun val) | |||||
Defined in PlutusCore.Evaluation.Machine.MachineParameters Associated Types
Methods from :: MachineParameters machinecosts fun val -> Rep (MachineParameters machinecosts fun val) x # to :: Rep (MachineParameters machinecosts fun val) x -> MachineParameters machinecosts fun val # | |||||
Generic (K a b) | |||||
Defined in Data.SOP.BasicFunctors Associated Types
| |||||
Generic (Tagged s b) | |||||
Defined in Data.Tagged Associated Types
| |||||
Generic (These1 f g a) | |||||
Defined in Data.Functor.These Associated Types
| |||||
Generic (Backwards f a) | |||||
Defined in Control.Applicative.Backwards Associated Types
| |||||
Generic (AccumT w m a) | |||||
Defined in Control.Monad.Trans.Accum Associated Types
| |||||
Generic (ExceptT e m a) | |||||
Defined in Control.Monad.Trans.Except Associated Types
| |||||
Generic (IdentityT f a) | |||||
Defined in Control.Monad.Trans.Identity Associated Types
| |||||
Generic (ReaderT r m a) | |||||
Defined in Control.Monad.Trans.Reader Associated Types
| |||||
Generic (SelectT r m a) | |||||
Defined in Control.Monad.Trans.Select Associated Types
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Lazy Associated Types
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.CPS Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Lazy Associated Types
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Strict Associated Types
| |||||
Generic (Constant a b) | |||||
Defined in Data.Functor.Constant Associated Types
| |||||
Generic (Reverse f a) | |||||
Defined in Data.Functor.Reverse Associated Types
| |||||
Generic (KVVector kv vv a) | |||||
Defined in Data.VMap.KVVector Associated Types
| |||||
Generic (a, b, c) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple4 a b c d) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (Product f g a) | |||||
Defined in Data.Functor.Product Associated Types
| |||||
Generic (Sum f g a) | |||||
Defined in Data.Functor.Sum Associated Types
| |||||
Generic (Tuple4 a b c d) | |||||
Defined in Foundation.Tuple Associated Types
| |||||
Generic ((f :*: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic ((f :+: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (K1 i c p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (VarDecl tyname name uni ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (TypeError term uni fun ann) | |||||
Defined in PlutusCore.Error Associated Types
| |||||
Generic (Program name uni fun ann) | |||||
Defined in UntypedPlutusCore.Core.Type Associated Types
| |||||
Generic (Term name uni fun ann) | |||||
Defined in UntypedPlutusCore.Core.Type Associated Types
| |||||
Generic (Subst name uni fun a) | |||||
Defined in UntypedPlutusCore.Transform.Inline Associated Types
| |||||
Generic (Datatype tyname name uni a) | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic (StreamBody' mods framing contentType a) | |||||
Defined in Servant.API.Stream Associated Types
Methods from :: StreamBody' mods framing contentType a -> Rep (StreamBody' mods framing contentType a) x # to :: Rep (StreamBody' mods framing contentType a) x -> StreamBody' mods framing contentType a # | |||||
Generic (Product2 f g x y) | |||||
Defined in Data.SOP.Functors Associated Types
| |||||
Generic (ContT r m a) | |||||
Defined in Control.Monad.Trans.Cont Associated Types
| |||||
Generic (VMap kv vv k v) | |||||
Defined in Data.VMap Associated Types
| |||||
Generic (a, b, c, d) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple5 a b c d e) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (Compose f g a) | |||||
Defined in Data.Functor.Compose Associated Types
| |||||
Generic (Clown f a b) | |||||
Defined in Data.Bifunctor.Clown Associated Types
| |||||
Generic (Flip p a b) | |||||
Defined in Data.Bifunctor.Flip Associated Types
| |||||
Generic (Joker g a b) | |||||
Defined in Data.Bifunctor.Joker Associated Types
| |||||
Generic (WrappedBifunctor p a b) | |||||
Defined in Data.Bifunctor.Wrapped Associated Types
Methods from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x # to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b # | |||||
Generic ((f :.: g) p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (M1 i c f p) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Program tyname name uni fun ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (Term tyname name uni fun ann) | |||||
Defined in PlutusCore.Core.Type Associated Types
| |||||
Generic (NormCheckError tyname name uni fun ann) | |||||
Defined in PlutusCore.Error Associated Types
Methods from :: NormCheckError tyname name uni fun ann -> Rep (NormCheckError tyname name uni fun ann) x # to :: Rep (NormCheckError tyname name uni fun ann) x -> NormCheckError tyname name uni fun ann # | |||||
Generic (Binding tyname name uni fun a) | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic (Program tyname name uni fun ann) | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic (Term tyname name uni fun a) | |||||
Defined in PlutusIR.Core.Type Associated Types
| |||||
Generic (InlinerState tyname name uni fun ann) | |||||
Defined in PlutusIR.Transform.Inline.Utils Associated Types
| |||||
Generic (BindingGrp tyname name uni fun a) | |||||
Defined in PlutusIR.Transform.LetFloatOut Associated Types
| |||||
Generic (Verb method statusCode contentTypes a) | |||||
Defined in Servant.API.Verbs | |||||
Generic ((f :.: g) p) | |||||
Defined in Data.SOP.BasicFunctors Associated Types
| |||||
Generic (Flip f x2 y2) | |||||
Defined in Data.SOP.Functors Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.CPS Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Lazy Associated Types
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Strict Associated Types
| |||||
Generic (a, b, c, d, e) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple6 a b c d e f) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (Product f g a b) | |||||
Defined in Data.Bifunctor.Product Associated Types
| |||||
Generic (Sum p q a b) | |||||
Defined in Data.Bifunctor.Sum Associated Types
| |||||
Generic (Stream method status framing contentType a) | |||||
Defined in Servant.API.Stream | |||||
Generic (a, b, c, d, e, f) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (STuple7 a b c d e f g) | |||||
Defined in Distribution.Utils.Structured Associated Types
| |||||
Generic (Tannen f p a b) | |||||
Defined in Data.Bifunctor.Tannen Associated Types
| |||||
Generic (a, b, c, d, e, f, g) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (Biff p f g a b) | |||||
Defined in Data.Bifunctor.Biff Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
Defined in GHC.Internal.Generics Associated Types
|
IsString
is used in combination with the -XOverloadedStrings
language extension to convert the literals to different string types.
For example, if you use the text package, you can say
{-# LANGUAGE OverloadedStrings #-} myText = "hello world" :: Text
Internally, the extension will convert this to the equivalent of
myText = fromString @Text ("hello world" :: String)
Note: You can use fromString
in normal code as well,
but the usual performance/memory efficiency problems with String
apply.
Methods
fromString :: String -> a #
Instances
IsString Key | |
Defined in Data.Aeson.Key Methods fromString :: String -> Key # | |
IsString Value | |
Defined in Data.Aeson.Types.Internal Methods fromString :: String -> Value # | |
IsString GYAddressBech32 # | |
Defined in GeniusYield.Types.Address Methods fromString :: String -> GYAddressBech32 # | |
IsString GYStakeAddressBech32 # | |
Defined in GeniusYield.Types.Address Methods | |
IsString GYDatumHash # | |
Defined in GeniusYield.Types.Datum Methods fromString :: String -> GYDatumHash # | |
IsString GYLogNamespace # | |
Defined in GeniusYield.Types.Logging Methods fromString :: String -> GYLogNamespace # | |
IsString LogSrc # | |
Defined in GeniusYield.Types.Logging Methods fromString :: String -> LogSrc # | |
IsString GYPubKeyHash # | |
Defined in GeniusYield.Types.PubKeyHash Methods fromString :: String -> GYPubKeyHash # | |
IsString GYMintingPolicyId # |
|
Defined in GeniusYield.Types.Script Methods fromString :: String -> GYMintingPolicyId # | |
IsString GYScriptHash # |
|
Defined in GeniusYield.Types.Script.ScriptHash Methods fromString :: String -> GYScriptHash # | |
IsString GYStakePoolIdBech32 # | |
Defined in GeniusYield.Types.StakePoolId Methods fromString :: String -> GYStakePoolIdBech32 # | |
IsString GYTime # |
|
Defined in GeniusYield.Types.Time Methods fromString :: String -> GYTime # | |
IsString GYTx # | |
Defined in GeniusYield.Types.Tx Methods fromString :: String -> GYTx # | |
IsString GYTxId # |
|
Defined in GeniusYield.Types.Tx Methods fromString :: String -> GYTxId # | |
IsString GYTxOutRef # |
|
Defined in GeniusYield.Types.TxOutRef Methods fromString :: String -> GYTxOutRef # | |
IsString GYAssetClass # | |
Defined in GeniusYield.Types.Value Methods fromString :: String -> GYAssetClass # | |
IsString GYTokenName # | Does NOT UTF8-encode. |
Defined in GeniusYield.Types.Value Methods fromString :: String -> GYTokenName # | |
IsString Alphabet | |
Defined in Data.ByteString.Base58.Internal Methods fromString :: String -> Alphabet # | |
IsString ByteString64 | |
Defined in Data.ByteString.Base64.Type Methods fromString :: String -> ByteString64 # | |
IsString AsciiString | |
Defined in Basement.Types.AsciiString Methods fromString :: String -> AsciiString # | |
IsString String | |
Defined in Basement.UTF8.Base Methods fromString :: String -> String # | |
IsString Project | |
Defined in Blockfrost.Auth Methods fromString :: String -> Project # | |
IsString Address | |
Defined in Blockfrost.Types.Shared.Address Methods fromString :: String -> Address # | |
IsString AssetId | |
Defined in Blockfrost.Types.Shared.AssetId Methods fromString :: String -> AssetId # | |
IsString BlockHash | |
Defined in Blockfrost.Types.Shared.BlockHash Methods fromString :: String -> BlockHash # | |
IsString DatumHash | |
Defined in Blockfrost.Types.Shared.DatumHash Methods fromString :: String -> DatumHash # | |
IsString PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId Methods fromString :: String -> PolicyId # | |
IsString PoolId | |
Defined in Blockfrost.Types.Shared.PoolId Methods fromString :: String -> PoolId # | |
IsString ScriptHash | |
Defined in Blockfrost.Types.Shared.ScriptHash Methods fromString :: String -> ScriptHash # | |
IsString TxHash | |
Defined in Blockfrost.Types.Shared.TxHash Methods fromString :: String -> TxHash # | |
IsString TxHashObject | |
Defined in Blockfrost.Types.Shared.TxHash Methods fromString :: String -> TxHashObject # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Lazy.Internal Methods fromString :: String -> ByteString # | |
IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal Methods fromString :: String -> ShortByteString # | |
IsString PraosNonce | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods fromString :: String -> PraosNonce # | |
IsString ScriptHash | |
Defined in Cardano.Api.Internal.Script Methods fromString :: String -> ScriptHash # | |
IsString TextEnvelopeDescr | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods fromString :: String -> TextEnvelopeDescr # | |
IsString TextEnvelopeType | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods fromString :: String -> TextEnvelopeType # | |
IsString TxId | |
Defined in Cardano.Api.Internal.TxIn Methods fromString :: String -> TxId # | |
IsString AssetName | |
Defined in Cardano.Api.Internal.Value Methods fromString :: String -> AssetName # | |
IsString PolicyId | |
Defined in Cardano.Api.Internal.Value Methods fromString :: String -> PolicyId # | |
IsString Seed | |
Defined in Crypto.Encoding.BIP39 Methods fromString :: String -> Seed # | |
IsString CheckpointsFile | |
Defined in Cardano.Node.Types Methods fromString :: String -> CheckpointsFile # | |
IsString GenesisFile | |
Defined in Cardano.Node.Types Methods fromString :: String -> GenesisFile # | |
IsString TmpAbsolutePath | |
Defined in Testnet.Filepath Methods fromString :: String -> TmpAbsolutePath # | |
IsString ByteArray | |
Defined in Codec.CBOR.ByteArray Methods fromString :: String -> ByteArray # | |
IsString SlicedByteArray | |
Defined in Codec.CBOR.ByteArray.Sliced Methods fromString :: String -> SlicedByteArray # | |
IsString GroupName | |
Defined in Hedgehog.Internal.Property Methods fromString :: String -> GroupName # | |
IsString LabelName | |
Defined in Hedgehog.Internal.Property Methods fromString :: String -> LabelName # | |
IsString PropertyName | |
Defined in Hedgehog.Internal.Property Methods fromString :: String -> PropertyName # | |
IsString Skip | We use this instance to support usage like withSkip "3:aB" It throws an error if the input is not a valid compressed |
Defined in Hedgehog.Internal.Property Methods fromString :: String -> Skip # | |
IsString RequestBody | Since 0.4.12 |
Defined in Network.HTTP.Client.Types Methods fromString :: String -> RequestBody # | |
IsString MediaType | |
Defined in Network.HTTP.Media.MediaType.Internal Methods fromString :: String -> MediaType # | |
IsString IP | |
Defined in Data.IP.Addr Methods fromString :: String -> IP # | |
IsString IPv4 | |
Defined in Data.IP.Addr Methods fromString :: String -> IPv4 # | |
IsString IPv6 | |
Defined in Data.IP.Addr Methods fromString :: String -> IPv6 # | |
IsString IPRange | |
Defined in Data.IP.Range Methods fromString :: String -> IPRange # | |
IsString Environment | |
Defined in Katip.Core Methods fromString :: String -> Environment # | |
IsString LogStr | |
Defined in Katip.Core Methods fromString :: String -> LogStr # | |
IsString Namespace | |
Defined in Katip.Core Methods fromString :: String -> Namespace # | |
IsString PolicyId | |
Defined in Maestro.Types.Common Methods fromString :: String -> PolicyId # | |
IsString TokenName | |
Defined in Maestro.Types.Common Methods fromString :: String -> TokenName # | |
IsString TxHash | |
Defined in Maestro.Types.Common Methods fromString :: String -> TxHash # | |
IsString NextCursor | |
Defined in Maestro.Types.V1.Common.Pagination Methods fromString :: String -> NextCursor # | |
IsString ScrubbedBytes | |
Defined in Data.ByteArray.ScrubbedBytes Methods fromString :: String -> ScrubbedBytes # | |
IsString License | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> License # | |
IsString Response | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> Response # | |
IsString Server | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> Server # | |
IsString Tag | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> Tag # | |
IsString UnliftingError | |
Defined in PlutusCore.Builtin.Result Methods fromString :: String -> UnliftingError # | |
IsString LedgerBytes | Read in arbitrary This is mostly used together with GHC's OverloadedStrings extension
to specify at the source code any IMPORTANT: the |
Defined in PlutusLedgerApi.V1.Bytes Methods fromString :: String -> LedgerBytes # | |
IsString PubKeyHash | from hex encoding |
Defined in PlutusLedgerApi.V1.Crypto Methods fromString :: String -> PubKeyHash # | |
IsString TxId | from hex encoding |
Defined in PlutusLedgerApi.V1.Data.Tx Methods fromString :: String -> TxId # | |
IsString CurrencySymbol | from hex encoding |
Defined in PlutusLedgerApi.V1.Data.Value Methods fromString :: String -> CurrencySymbol # | |
IsString TokenName | UTF-8 encoding. Doesn't verify length. |
Defined in PlutusLedgerApi.V1.Data.Value Methods fromString :: String -> TokenName # | |
IsString DatumHash | from hex encoding |
Defined in PlutusLedgerApi.V1.Scripts Methods fromString :: String -> DatumHash # | |
IsString RedeemerHash | from hex encoding |
Defined in PlutusLedgerApi.V1.Scripts Methods fromString :: String -> RedeemerHash # | |
IsString ScriptHash | from hex encoding |
Defined in PlutusLedgerApi.V1.Scripts Methods fromString :: String -> ScriptHash # | |
IsString TxId | from hex encoding |
Defined in PlutusLedgerApi.V1.Tx Methods fromString :: String -> TxId # | |
IsString TxId | from hex encoding |
Defined in PlutusLedgerApi.V3.Data.Tx Methods fromString :: String -> TxId # | |
IsString TxId | from hex encoding |
Defined in PlutusLedgerApi.V3.Tx Methods fromString :: String -> TxId # | |
IsString BuiltinByteStringHex | |
Defined in PlutusTx.Builtins.HasOpaque Methods | |
IsString BuiltinByteStringUtf8 | |
Defined in PlutusTx.Builtins.HasOpaque Methods | |
IsString Identifier | |
Defined in Database.PostgreSQL.Simple.Types Methods fromString :: String -> Identifier # | |
IsString QualifiedIdentifier |
|
Defined in Database.PostgreSQL.Simple.Types Methods fromString :: String -> QualifiedIdentifier # | |
IsString Query | |
Defined in Database.PostgreSQL.Simple.Types Methods fromString :: String -> Query # | |
IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ Methods fromString :: String -> Doc # | |
IsString Host | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Host # | |
IsString License | |
Defined in Data.Swagger.Internal Methods fromString :: String -> License # | |
IsString Response | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Response # | |
IsString Tag | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Tag # | |
IsString Builder | Performs replacement on invalid scalar values:
|
Defined in Data.Text.Internal.Builder Methods fromString :: String -> Builder # | |
IsString ShortText | Note: Surrogate pairs ( |
Defined in Data.Text.Short.Internal Methods fromString :: String -> ShortText # | |
IsString (Encoding' a) | Since: aeson-2.2.0.0 |
Defined in Data.Aeson.Encoding.Internal Methods fromString :: String -> Encoding' a # | |
IsString a => IsString (Graph a) | |
Defined in Algebra.Graph Methods fromString :: String -> Graph a # | |
IsString a => IsString (AdjacencyMap a) | |
Defined in Algebra.Graph.AdjacencyMap Methods fromString :: String -> AdjacencyMap a # | |
IsString a => IsString (AdjacencyMap a) | |
Defined in Algebra.Graph.NonEmpty.AdjacencyMap Methods fromString :: String -> AdjacencyMap a # | |
IsString a => IsString (Relation a) | |
Defined in Algebra.Graph.Relation Methods fromString :: String -> Relation a # | |
IsString a => IsString (Relation a) | |
Defined in Algebra.Graph.Relation.Symmetric Methods fromString :: String -> Relation a # | |
IsString a => IsString (Graph a) | |
Defined in Algebra.Graph.Undirected Methods fromString :: String -> Graph a # | |
IsString (GYExtendedSigningKey kr) # | |
Defined in GeniusYield.Types.Key Methods fromString :: String -> GYExtendedSigningKey kr # | |
IsString (GYExtendedVerificationKey kr) # | |
Defined in GeniusYield.Types.Key Methods fromString :: String -> GYExtendedVerificationKey kr # | |
IsString (GYSigningKey kr) # | |
Defined in GeniusYield.Types.Key Methods fromString :: String -> GYSigningKey kr # | |
IsString (GYVerificationKey kr) # | |
Defined in GeniusYield.Types.Key Methods fromString :: String -> GYVerificationKey kr # | |
IsString (GYKeyHash kr) # | |
Defined in GeniusYield.Types.KeyHash Methods fromString :: String -> GYKeyHash kr # | |
IsString (GYVRFVerKeyHash kr) # |
|
Defined in GeniusYield.Types.KeyHash Methods fromString :: String -> GYVRFVerKeyHash kr # | |
IsString (Hash BlockHeader) | |
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader # | |
IsString (Hash GovernancePoll) | |
Defined in Cardano.Api.Internal.Governance.Poll Methods fromString :: String -> Hash GovernancePoll # | |
IsString (Hash ByronKey) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKey # | |
IsString (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKeyLegacy # | |
IsString (Hash KesKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> Hash KesKey # | |
IsString (Hash VrfKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> Hash VrfKey # | |
IsString (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdKey # | |
IsString (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotKey # | |
IsString (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash DRepExtendedKey # | |
IsString (Hash DRepKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash DRepKey # | |
IsString (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisDelegateKey # | |
IsString (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisExtendedKey # | |
IsString (Hash GenesisKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisKey # | |
IsString (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisUTxOKey # | |
IsString (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentExtendedKey # | |
IsString (Hash PaymentKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentKey # | |
IsString (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeExtendedKey # | |
IsString (Hash StakeKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeKey # | |
IsString (Hash StakePoolKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakePoolKey # | |
IsString (Hash ScriptData) | |
Defined in Cardano.Api.Internal.ScriptData Methods fromString :: String -> Hash ScriptData # | |
IsString (SigningKey ByronKey) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> SigningKey ByronKey # | |
IsString (SigningKey ByronKeyLegacy) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods | |
IsString (SigningKey KesKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey KesKey # | |
IsString (SigningKey VrfKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey VrfKey # | |
IsString (SigningKey CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdExtendedKey # | |
IsString (SigningKey CommitteeColdKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeHotExtendedKey # | |
IsString (SigningKey CommitteeHotKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey DRepExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey DRepKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey DRepKey # | |
IsString (SigningKey GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateExtendedKey # | |
IsString (SigningKey GenesisDelegateKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey GenesisExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey GenesisKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisKey # | |
IsString (SigningKey GenesisUTxOKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey PaymentExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey PaymentKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentKey # | |
IsString (SigningKey StakeExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey StakeKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeKey # | |
IsString (SigningKey StakePoolExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (SigningKey StakePoolKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakePoolKey # | |
IsString (VerificationKey ByronKey) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> VerificationKey ByronKey # | |
IsString (VerificationKey ByronKeyLegacy) | |
Defined in Cardano.Api.Internal.Keys.Byron Methods | |
IsString (VerificationKey KesKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey KesKey # | |
IsString (VerificationKey VrfKey) | |
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey VrfKey # | |
IsString (VerificationKey CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdExtendedKey # | |
IsString (VerificationKey CommitteeColdKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotExtendedKey # | |
IsString (VerificationKey CommitteeHotKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey DRepExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey DRepKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey DRepKey # | |
IsString (VerificationKey GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateExtendedKey # | |
IsString (VerificationKey GenesisDelegateKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateKey # | |
IsString (VerificationKey GenesisExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisExtendedKey # | |
IsString (VerificationKey GenesisKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey GenesisUTxOKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey PaymentExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey PaymentExtendedKey # | |
IsString (VerificationKey PaymentKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey StakeExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
IsString (VerificationKey StakeKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakeKey # | |
IsString (VerificationKey StakePoolExtendedKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolExtendedKey # | |
IsString (VerificationKey StakePoolKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |
(IsString s, FoldCase s) => IsString (CI s) | |
Defined in Data.CaseInsensitive.Internal Methods fromString :: String -> CI s # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
a ~ Char => IsString (DNonEmpty a) | |
Defined in Data.DList.DNonEmpty.Internal Methods fromString :: String -> DNonEmpty a # | |
a ~ Char => IsString (DList a) | |
Defined in Data.DList.Internal Methods fromString :: String -> DList a # | |
IsString a => IsString (Identity a) | @since base-4.9.0.0 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> Identity a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class Methods fromString :: String -> Hashed a # | |
IsString (AddrRange IPv4) | |
Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv4 # | |
IsString (AddrRange IPv6) | |
Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv6 # | |
IsString (Bech32StringOf a) | |
Defined in Maestro.Types.Common Methods fromString :: String -> Bech32StringOf a # | |
IsString (HashStringOf a) | |
Defined in Maestro.Types.Common Methods fromString :: String -> HashStringOf a # | |
IsString (HexStringOf a) | |
Defined in Maestro.Types.Common Methods fromString :: String -> HexStringOf a # | |
IsString (TaggedText description) | |
Defined in Maestro.Types.V1.Common Methods fromString :: String -> TaggedText description # | |
IsString a => IsString (Referenced a) | |
Defined in Data.OpenApi.Internal Methods fromString :: String -> Referenced a # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fromString :: String -> Doc a # | |
IsString (Doc ann) |
This instance uses the |
Defined in Prettyprinter.Internal Methods fromString :: String -> Doc ann # | |
IsString a => IsString (Referenced a) | |
Defined in Data.Swagger.Internal Methods fromString :: String -> Referenced a # | |
HashAlgorithm h => IsString (Q (TExp (Hash h a))) | This instance is meant to be used with
|
Defined in Cardano.Crypto.Hash.Class | |
KnownNat n => IsString (Q (TExp (PinnedSizedBytes n))) | This instance is meant to be used with
|
Defined in Cardano.Crypto.PinnedSizedBytes Methods fromString :: String -> Q (TExp (PinnedSizedBytes n)) # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.WL Methods fromString :: String -> Doc a # | |
a ~ Char => IsString [a] |
@since base-2.01 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> [a] # | |
IsString a => IsString (Graph e a) | |
Defined in Algebra.Graph.Labelled Methods fromString :: String -> Graph e a # | |
IsString a => IsString (AdjacencyMap e a) | |
Defined in Algebra.Graph.Labelled.AdjacencyMap Methods fromString :: String -> AdjacencyMap e a # | |
IsString (File content direction) | |
Defined in Cardano.Api.Internal.IO.Base Methods fromString :: String -> File content direction # | |
HashAlgorithm h => IsString (Hash h a) | |
Defined in Cardano.Crypto.Hash.Class Methods fromString :: String -> Hash h a # | |
IsString a => IsString (Const a b) | @since base-4.9.0.0 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> Const a b # | |
IsString a => IsString (Tagged s a) | |
Defined in Data.Tagged Methods fromString :: String -> Tagged s a # | |
HashAlgorithm h => IsString (Code Q (Hash h a)) | |
Defined in Cardano.Crypto.Hash.Class | |
KnownNat n => IsString (Code Q (PinnedSizedBytes n)) | |
Defined in Cardano.Crypto.PinnedSizedBytes Methods fromString :: String -> Code Q (PinnedSizedBytes n) # |
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signalling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signalling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>>
safeDiv 4 0
Nothing
>>>
safeDiv 4 2
Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Example
>>>
liftA2 (,) (Just 3) (Just 5)
Just (3,5)
>>>
liftA2 (+) [1, 2, 3] [4, 5, 6]
[5,6,7,6,7,8,7,8,9]
Since Void
values logically don't exist, this witnesses the
logical reasoning tool of "ex falso quodlibet".
>>>
let x :: Either Void Int; x = Right 5
>>>
:{
case x of Right r -> r Left l -> absurd l :} 5
@since base-4.8.0.0
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
Examples
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
>>>
putStr "pi:" >> when False (print 3.14159)
pi:
fromMaybe :: a -> Maybe a -> a #
The fromMaybe
function takes a default value and a Maybe
value. If the Maybe
is Nothing
, it returns the default value;
otherwise, it returns the value contained in the Maybe
.
Examples
Basic usage:
>>>
fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>>
fromMaybe "" Nothing
""
Read an integer from a string using readMaybe
. If we fail to
parse an integer, we want to return 0
by default:
>>>
import GHC.Internal.Text.Read ( readMaybe )
>>>
fromMaybe 0 (readMaybe "5")
5>>>
fromMaybe 0 (readMaybe "")
0
mapMaybe :: Filterable f => (a -> Maybe b) -> f a -> f b #
Like mapMaybe
.
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 #
runs the binary function on
b u x yb
on the results of applying
unary function u
to two arguments x
and y
. From the opposite
perspective, it transforms two inputs and combines the outputs.
(op `on
` f) x y = f x `op
` f y
Examples
>>>
sortBy (compare `on` length) [[0, 1, 2], [0, 1], [], [0]]
[[],[0],[0,1],[0,1,2]]
>>>
((+) `on` length) [1, 2, 3] [-1]
4
>>>
((,) `on` (*2)) 2 3
(4,6)
Algebraic properties
isAlphaNum :: Char -> Bool #
Selects alphabetic or numeric Unicode characters.
Note that numeric digits outside the ASCII range, as well as numeric
characters which aren't digits, are selected by this function but not by
isDigit
. Such characters may be part of identifiers but are not used by
the printer and reader to represent numbers, e.g., Roman numerals like
,
full-width digits like V
'1'
(aka '65297'
).
This function returns True
if its argument has one of the
following GeneralCategory
s, or False
otherwise:
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Constructors
Proxy |
Instances
ApplicativeB (Proxy :: (k -> Type) -> Type) | |
ConstraintsB (Proxy :: (k -> Type) -> Type) | |
DistributiveB (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.DistributiveB | |
FunctorB (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
TraversableB (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB Methods btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> Proxy f -> e (Proxy g) # | |
Generic1 (Proxy :: k -> Type) | |
Defined in GHC.Internal.Generics | |
FoldableWithIndex Void (Proxy :: Type -> Type) | |
Defined in WithIndex | |
FunctorWithIndex Void (Proxy :: Type -> Type) | |
TraversableWithIndex Void (Proxy :: Type -> Type) | |
EqP (Proxy :: k -> Type) | |
OrdP (Proxy :: k -> Type) | |
FilterableWithIndex Void (Proxy :: Type -> Type) | |
WitherableWithIndex Void (Proxy :: Type -> Type) | |
Representable (Proxy :: Type -> Type) | |
FromJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Proxy a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding # liftOmitField :: (a -> Bool) -> Proxy a -> Bool # | |
MonadZip (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Contravariant (Proxy :: Type -> Type) | |
NFData1 (Proxy :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Alternative (Proxy :: Type -> Type) | @since base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) | @since base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | @since base-4.7.0.0 |
Monad (Proxy :: Type -> Type) | @since base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | @since base-4.9.0.0 |
Foldable (Proxy :: Type -> Type) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | @since base-4.7.0.0 |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
CollectScopeInfo (Proxy :: Type -> Type) | |
Defined in PlutusCore.Check.Scoping Methods | |
EstablishScoping (Proxy :: Type -> Type) | |
Defined in PlutusCore.Check.Scoping | |
Filterable (Proxy :: Type -> Type) | |
Witherable (Proxy :: Type -> Type) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Proxy a -> f (Proxy b) # witherM :: Monad m => (a -> m (Maybe b)) -> Proxy a -> m (Proxy b) # filterA :: Applicative f => (a -> f Bool) -> Proxy a -> f (Proxy a) # witherMap :: Applicative m => (Proxy b -> r) -> (a -> m (Maybe b)) -> Proxy a -> m r # | |
FromJSON (Proxy a) | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON (Proxy a) | |
Default (Proxy a) | |
Defined in Data.Default.Internal | |
NFData (Proxy a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Monoid (Proxy s) | @since base-4.7.0.0 |
Semigroup (Proxy s) | @since base-4.9.0.0 |
Bounded (Proxy t) | @since base-4.7.0.0 |
Enum (Proxy s) | @since base-4.7.0.0 |
Generic (Proxy t) | |
Defined in GHC.Internal.Generics | |
Ix (Proxy s) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Proxy | |
Read (Proxy t) | @since base-4.7.0.0 |
Show (Proxy s) | @since base-4.7.0.0 |
Eq (Proxy s) | @since base-4.7.0.0 |
Ord (Proxy s) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Proxy | |
Abelian (Proxy x) | |
Defined in Data.Group | |
Cyclic (Proxy x) | |
Defined in Data.Group | |
Group (Proxy x) | Trivial group, Functor style. |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
MonoFoldable (Proxy a) | Since: mono-traversable-1.0.11.0 |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Proxy a) -> m) -> Proxy a -> m # ofoldr :: (Element (Proxy a) -> b -> b) -> b -> Proxy a -> b # ofoldl' :: (a0 -> Element (Proxy a) -> a0) -> a0 -> Proxy a -> a0 # otoList :: Proxy a -> [Element (Proxy a)] # oall :: (Element (Proxy a) -> Bool) -> Proxy a -> Bool # oany :: (Element (Proxy a) -> Bool) -> Proxy a -> Bool # olength64 :: Proxy a -> Int64 # ocompareLength :: Integral i => Proxy a -> i -> Ordering # otraverse_ :: Applicative f => (Element (Proxy a) -> f b) -> Proxy a -> f () # ofor_ :: Applicative f => Proxy a -> (Element (Proxy a) -> f b) -> f () # omapM_ :: Applicative m => (Element (Proxy a) -> m ()) -> Proxy a -> m () # oforM_ :: Applicative m => Proxy a -> (Element (Proxy a) -> m ()) -> m () # ofoldlM :: Monad m => (a0 -> Element (Proxy a) -> m a0) -> a0 -> Proxy a -> m a0 # ofoldMap1Ex :: Semigroup m => (Element (Proxy a) -> m) -> Proxy a -> m # ofoldr1Ex :: (Element (Proxy a) -> Element (Proxy a) -> Element (Proxy a)) -> Proxy a -> Element (Proxy a) # ofoldl1Ex' :: (Element (Proxy a) -> Element (Proxy a) -> Element (Proxy a)) -> Proxy a -> Element (Proxy a) # headEx :: Proxy a -> Element (Proxy a) # lastEx :: Proxy a -> Element (Proxy a) # unsafeHead :: Proxy a -> Element (Proxy a) # unsafeLast :: Proxy a -> Element (Proxy a) # maximumByEx :: (Element (Proxy a) -> Element (Proxy a) -> Ordering) -> Proxy a -> Element (Proxy a) # minimumByEx :: (Element (Proxy a) -> Element (Proxy a) -> Ordering) -> Proxy a -> Element (Proxy a) # | |
MonoFunctor (Proxy a) | Since: mono-traversable-1.0.11.0 |
MonoPointed (Proxy a) | Since: mono-traversable-1.0.11.0 |
MonoTraversable (Proxy a) | Since: mono-traversable-1.0.11.0 |
MonoidNull (Proxy a) | Since: monoid-subclasses-1.2.5.0 |
Defined in Data.Monoid.Null | |
PositiveMonoid (Proxy a) | Since: monoid-subclasses-1.2.5.0 |
Defined in Data.Monoid.Null | |
Serialise (Proxy a) | Since: serialise-0.2.0.0 |
type AllB (c :: k -> Constraint) (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.ConstraintsB | |
type Rep1 (Proxy :: k -> Type) | @since base-4.6.0.0 |
type Rep (Proxy :: Type -> Type) | |
type Code (Proxy t) | |
Defined in Generics.SOP.Instances | |
type DatatypeInfoOf (Proxy t) | |
Defined in Generics.SOP.Instances type DatatypeInfoOf (Proxy t) = 'ADT "GHC.Internal.Data.Proxy" "Proxy" '['Constructor "Proxy"] '['[] :: [StrictnessInfo]] | |
type Rep (Proxy t) | @since base-4.6.0.0 |
type Element (Proxy a) | |
Defined in Data.MonoTraversable |
class (Typeable e, Show e) => Exception e #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving Show instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Instances
Exception ImpException | |
Defined in Test.ImpSpec.Internal Methods toException :: ImpException -> SomeException # fromException :: SomeException -> Maybe ImpException # displayException :: ImpException -> String # backtraceDesired :: ImpException -> Bool # | |
Exception AesonException | |
Defined in Data.Aeson.Types.Internal Methods toException :: AesonException -> SomeException # fromException :: SomeException -> Maybe AesonException # displayException :: AesonException -> String # backtraceDesired :: AesonException -> Bool # | |
Exception AsyncCancelled | |
Defined in Control.Concurrent.Async.Internal Methods toException :: AsyncCancelled -> SomeException # fromException :: SomeException -> Maybe AsyncCancelled # displayException :: AsyncCancelled -> String # backtraceDesired :: AsyncCancelled -> Bool # | |
Exception ExceptionInLinkedThread | |
Exception CardanoQueryException # | |
Defined in GeniusYield.CardanoApi.Query | |
Exception GYApiError # | |
Defined in GeniusYield.HTTP.Errors Methods toException :: GYApiError -> SomeException # fromException :: SomeException -> Maybe GYApiError # displayException :: GYApiError -> String # backtraceDesired :: GYApiError -> Bool # | |
Exception SubmitTxException # | |
Defined in GeniusYield.Providers.Common Methods toException :: SubmitTxException -> SomeException # fromException :: SomeException -> Maybe SubmitTxException # | |
Exception OgmiosProviderException # | |
Defined in GeniusYield.Providers.Ogmios | |
Exception GYTxMonadException # | |
Defined in GeniusYield.TxBuilder.Errors Methods toException :: GYTxMonadException -> SomeException # fromException :: SomeException -> Maybe GYTxMonadException # | |
Exception GYAwaitTxException # | |
Defined in GeniusYield.Types.Providers Methods toException :: GYAwaitTxException -> SomeException # fromException :: SomeException -> Maybe GYAwaitTxException # | |
Exception Timeout | Since: base-4.7.0.0 |
Defined in System.Timeout Methods toException :: Timeout -> SomeException # fromException :: SomeException -> Maybe Timeout # displayException :: Timeout -> String # backtraceDesired :: Timeout -> Bool # | |
Exception ASCII7_Invalid | |
Defined in Basement.String.Encoding.ASCII7 Methods toException :: ASCII7_Invalid -> SomeException # fromException :: SomeException -> Maybe ASCII7_Invalid # displayException :: ASCII7_Invalid -> String # backtraceDesired :: ASCII7_Invalid -> Bool # | |
Exception ISO_8859_1_Invalid | |
Defined in Basement.String.Encoding.ISO_8859_1 Methods toException :: ISO_8859_1_Invalid -> SomeException # fromException :: SomeException -> Maybe ISO_8859_1_Invalid # displayException :: ISO_8859_1_Invalid -> String # backtraceDesired :: ISO_8859_1_Invalid -> Bool # | |
Exception UTF16_Invalid | |
Defined in Basement.String.Encoding.UTF16 Methods toException :: UTF16_Invalid -> SomeException # fromException :: SomeException -> Maybe UTF16_Invalid # displayException :: UTF16_Invalid -> String # backtraceDesired :: UTF16_Invalid -> Bool # | |
Exception UTF32_Invalid | |
Defined in Basement.String.Encoding.UTF32 Methods toException :: UTF32_Invalid -> SomeException # fromException :: SomeException -> Maybe UTF32_Invalid # displayException :: UTF32_Invalid -> String # backtraceDesired :: UTF32_Invalid -> Bool # | |
Exception HumanReadablePartError | |
Defined in Codec.Binary.Bech32.Internal | |
Exception BimapException | |
Defined in Data.Bimap Methods toException :: BimapException -> SomeException # fromException :: SomeException -> Maybe BimapException # displayException :: BimapException -> String # backtraceDesired :: BimapException -> Bool # | |
Exception SizeOverflowException | |
Defined in Data.ByteString.Internal.Type | |
Exception ErrInspectAddress | |
Defined in Cardano.Address.Style.Byron Methods toException :: ErrInspectAddress -> SomeException # fromException :: SomeException -> Maybe ErrInspectAddress # | |
Exception ErrInspectAddress | |
Defined in Cardano.Address.Style.Icarus Methods toException :: ErrInspectAddress -> SomeException # fromException :: SomeException -> Maybe ErrInspectAddress # | |
Exception ErrInspectAddress | |
Defined in Cardano.Address.Style.Shelley Methods toException :: ErrInspectAddress -> SomeException # fromException :: SomeException -> Maybe ErrInspectAddress # | |
Exception ErrInspectAddressOnlyShelley | |
Exception ErrorAsException | |
Defined in Cardano.Api.Internal.Error Methods toException :: ErrorAsException -> SomeException # fromException :: SomeException -> Maybe ErrorAsException # | |
Exception AlonzoGenesisError | |
Defined in Cardano.Api.Internal.LedgerState Methods toException :: AlonzoGenesisError -> SomeException # fromException :: SomeException -> Maybe AlonzoGenesisError # displayException :: AlonzoGenesisError -> String # backtraceDesired :: AlonzoGenesisError -> Bool # | |
Exception ConwayGenesisError | |
Defined in Cardano.Api.Internal.LedgerState Methods toException :: ConwayGenesisError -> SomeException # fromException :: SomeException -> Maybe ConwayGenesisError # displayException :: ConwayGenesisError -> String # backtraceDesired :: ConwayGenesisError -> Bool # | |
Exception GenesisConfigError | |
Defined in Cardano.Api.Internal.LedgerState Methods toException :: GenesisConfigError -> SomeException # fromException :: SomeException -> Maybe GenesisConfigError # | |
Exception InitialLedgerStateError | |
Exception LedgerStateError | |
Defined in Cardano.Api.Internal.LedgerState Methods toException :: LedgerStateError -> SomeException # fromException :: SomeException -> Maybe LedgerStateError # | |
Exception ShelleyGenesisError | |
Defined in Cardano.Api.Internal.LedgerState Methods toException :: ShelleyGenesisError -> SomeException # fromException :: SomeException -> Maybe ShelleyGenesisError # displayException :: ShelleyGenesisError -> String # backtraceDesired :: ShelleyGenesisError -> Bool # | |
Exception DecoderError | |
Defined in Cardano.Binary.FromCBOR Methods toException :: DecoderError -> SomeException # fromException :: SomeException -> Maybe DecoderError # displayException :: DecoderError -> String # backtraceDesired :: DecoderError -> Bool # | |
Exception SizeCheckException | |
Defined in Cardano.Crypto.DirectSerialise Methods toException :: SizeCheckException -> SomeException # fromException :: SomeException -> Maybe SizeCheckException # | |
Exception AllocatorException | |
Defined in Cardano.Crypto.Libsodium.Memory.Internal Methods toException :: AllocatorException -> SomeException # fromException :: SomeException -> Maybe AllocatorException # displayException :: AllocatorException -> String # backtraceDesired :: AllocatorException -> Bool # | |
Exception SeedBytesExhausted | |
Defined in Cardano.Crypto.Seed Methods toException :: SeedBytesExhausted -> SomeException # fromException :: SomeException -> Maybe SeedBytesExhausted # | |
Exception EpochErr | |
Defined in Cardano.Ledger.BaseTypes Methods toException :: EpochErr -> SomeException # fromException :: SomeException -> Maybe EpochErr # displayException :: EpochErr -> String # backtraceDesired :: EpochErr -> Bool # | |
Exception SocketConfigError | |
Defined in Cardano.Node.Configuration.Socket Methods toException :: SocketConfigError -> SomeException # fromException :: SomeException -> Maybe SocketConfigError # | |
Exception ConfigError | |
Defined in Cardano.Node.Types Methods toException :: ConfigError -> SomeException # fromException :: SomeException -> Maybe ConfigError # displayException :: ConfigError -> String # backtraceDesired :: ConfigError -> Bool # | |
Exception VRFPrivateKeyFilePermissionError | |
Defined in Cardano.Node.Types | |
Exception PingClientError | |
Defined in Cardano.Network.Ping Methods toException :: PingClientError -> SomeException # fromException :: SomeException -> Maybe PingClientError # displayException :: PingClientError -> String # backtraceDesired :: PingClientError -> Bool # | |
Exception DeserialiseFailure | |
Defined in Codec.CBOR.Read Methods toException :: DeserialiseFailure -> SomeException # fromException :: SomeException -> Maybe DeserialiseFailure # | |
Exception CryptoError | |
Defined in Crypto.Error.Types Methods toException :: CryptoError -> SomeException # fromException :: SomeException -> Maybe CryptoError # displayException :: CryptoError -> String # backtraceDesired :: CryptoError -> Bool # | |
Exception CryptoError | |
Defined in Crypto.Error.Types Methods toException :: CryptoError -> SomeException # fromException :: SomeException -> Maybe CryptoError # displayException :: CryptoError -> String # backtraceDesired :: CryptoError -> Bool # | |
Exception DNSError | |
Defined in Network.DNS.Types.Internal Methods toException :: DNSError -> SomeException # fromException :: SomeException -> Maybe DNSError # displayException :: DNSError -> String # backtraceDesired :: DNSError -> Bool # | |
Exception Timeout | |
Defined in System.Time.Extra Methods toException :: Timeout -> SomeException # fromException :: SomeException -> Maybe Timeout # displayException :: Timeout -> String # backtraceDesired :: Timeout -> Bool # | |
Exception FsError | |
Defined in System.FS.API.Types Methods toException :: FsError -> SomeException # fromException :: SomeException -> Maybe FsError # displayException :: FsError -> String # backtraceDesired :: FsError -> Bool # | |
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 # | |
Exception NestedAtomically | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NestedAtomically -> SomeException # fromException :: SomeException -> Maybe NestedAtomically # | |
Exception NoMatchingContinuationPrompt | @since base-4.18 |
Defined in GHC.Internal.Control.Exception.Base | |
Exception NoMethodError | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NoMethodError -> SomeException # fromException :: SomeException -> Maybe NoMethodError # displayException :: NoMethodError -> String # backtraceDesired :: NoMethodError -> Bool # | |
Exception NonTermination | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NonTermination -> SomeException # fromException :: SomeException -> Maybe NonTermination # displayException :: NonTermination -> String # backtraceDesired :: NonTermination -> Bool # | |
Exception PatternMatchFail | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: PatternMatchFail -> SomeException # fromException :: SomeException -> Maybe PatternMatchFail # | |
Exception RecConError | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecConError -> SomeException # fromException :: SomeException -> Maybe RecConError # displayException :: RecConError -> String # backtraceDesired :: RecConError -> Bool # | |
Exception RecSelError | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecSelError -> SomeException # fromException :: SomeException -> Maybe RecSelError # displayException :: RecSelError -> String # backtraceDesired :: RecSelError -> Bool # | |
Exception RecUpdError | @since base-4.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecUpdError -> SomeException # fromException :: SomeException -> Maybe RecUpdError # displayException :: RecUpdError -> String # backtraceDesired :: RecUpdError -> Bool # | |
Exception TypeError | @since base-4.9.0.0 |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: TypeError -> SomeException # fromException :: SomeException -> Maybe TypeError # displayException :: TypeError -> String # backtraceDesired :: TypeError -> Bool # | |
Exception ArithException | @since base-4.0.0.0 |
Defined in GHC.Internal.Exception.Type Methods toException :: ArithException -> SomeException # fromException :: SomeException -> Maybe ArithException # displayException :: ArithException -> String # backtraceDesired :: ArithException -> Bool # | |
Exception SomeException | This drops any attached @since base-3.0 |
Defined in GHC.Internal.Exception.Type Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String # backtraceDesired :: SomeException -> Bool # | |
Exception AllocationLimitExceeded | @since base-4.8.0.0 |
Defined in GHC.Internal.IO.Exception | |
Exception ArrayException | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: ArrayException -> SomeException # fromException :: SomeException -> Maybe ArrayException # displayException :: ArrayException -> String # backtraceDesired :: ArrayException -> Bool # | |
Exception AssertionFailed | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: AssertionFailed -> SomeException # fromException :: SomeException -> Maybe AssertionFailed # displayException :: AssertionFailed -> String # backtraceDesired :: AssertionFailed -> Bool # | |
Exception AsyncException | @since base-4.7.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: AsyncException -> SomeException # fromException :: SomeException -> Maybe AsyncException # displayException :: AsyncException -> String # backtraceDesired :: AsyncException -> Bool # | |
Exception BlockedIndefinitelyOnMVar | @since base-4.1.0.0 |
Exception BlockedIndefinitelyOnSTM | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception | |
Exception CompactionFailed | @since base-4.10.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: CompactionFailed -> SomeException # fromException :: SomeException -> Maybe CompactionFailed # | |
Exception Deadlock | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: Deadlock -> SomeException # fromException :: SomeException -> Maybe Deadlock # displayException :: Deadlock -> String # backtraceDesired :: Deadlock -> Bool # | |
Exception ExitCode | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # backtraceDesired :: ExitCode -> Bool # | |
Exception FixIOException | @since base-4.11.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: FixIOException -> SomeException # fromException :: SomeException -> Maybe FixIOException # displayException :: FixIOException -> String # backtraceDesired :: FixIOException -> Bool # | |
Exception IOException | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String # backtraceDesired :: IOException -> Bool # | |
Exception SomeAsyncException | @since base-4.7.0.0 |
Defined in GHC.Internal.IO.Exception Methods toException :: SomeAsyncException -> SomeException # fromException :: SomeException -> Maybe SomeAsyncException # | |
Exception WatchdogException | |
Defined in Hedgehog.Extras.Test.TestWatchdog Methods toException :: WatchdogException -> SomeException # fromException :: SomeException -> Maybe WatchdogException # | |
Exception ResultStatus | |
Defined in Test.Hspec.Core.Example Methods toException :: ResultStatus -> SomeException # fromException :: SomeException -> Maybe ResultStatus # displayException :: ResultStatus -> String # backtraceDesired :: ResultStatus -> Bool # | |
Exception EncapsulatedPopperException | |
Defined in Network.HTTP.Client.Request Methods toException :: EncapsulatedPopperException -> SomeException # fromException :: SomeException -> Maybe EncapsulatedPopperException # displayException :: EncapsulatedPopperException -> String # backtraceDesired :: EncapsulatedPopperException -> Bool # | |
Exception HttpException | |
Defined in Network.HTTP.Client.Types Methods toException :: HttpException -> SomeException # fromException :: SomeException -> Maybe HttpException # displayException :: HttpException -> String # backtraceDesired :: HttpException -> Bool # | |
Exception HttpExceptionContentWrapper | |
Defined in Network.HTTP.Client.Types Methods toException :: HttpExceptionContentWrapper -> SomeException # fromException :: SomeException -> Maybe HttpExceptionContentWrapper # displayException :: HttpExceptionContentWrapper -> String # backtraceDesired :: HttpExceptionContentWrapper -> Bool # | |
Exception DigestAuthException | |
Defined in Network.HTTP.Client.TLS | |
Exception ExceptionInLinkedThread | |
Defined in Control.Monad.Class.MonadAsync | |
Exception BlockedIndefinitely | |
Defined in Control.Monad.Class.MonadSTM.Internal Methods toException :: BlockedIndefinitely -> SomeException # fromException :: SomeException -> Maybe BlockedIndefinitely # displayException :: BlockedIndefinitely -> String # backtraceDesired :: BlockedIndefinitely -> Bool # | |
Exception GenericBackendFailure | |
Defined in Cardano.BM.Data.Backend | |
Exception HandlingException | |
Defined in Control.Lens.Internal.Exception Methods toException :: HandlingException -> SomeException # fromException :: SomeException -> Maybe HandlingException # | |
Exception MaestroError | |
Defined in Maestro.Client.Error Methods toException :: MaestroError -> SomeException # fromException :: SomeException -> Maybe MaestroError # displayException :: MaestroError -> String # backtraceDesired :: MaestroError -> Bool # | |
Exception DataMeasureClassOverflowException | |
Defined in Data.Measure.Class | |
Exception InvalidPosException | |
Defined in Text.Megaparsec.Pos | |
Exception Error | |
Defined in Network.Mux.Trace Methods toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # backtraceDesired :: Error -> Bool # | |
Exception RuntimeError | |
Defined in Network.Mux.Types Methods toException :: RuntimeError -> SomeException # fromException :: SomeException -> Maybe RuntimeError # displayException :: RuntimeError -> String # backtraceDesired :: RuntimeError -> Bool # | |
Exception SanityCheckIssue | |
Defined in Ouroboros.Consensus.Block.SupportsSanityCheck Methods toException :: SanityCheckIssue -> SomeException # fromException :: SomeException -> Maybe SanityCheckIssue # | |
Exception SystemClockMovedBackException | |
Exception OutsideForecastRange | |
Defined in Ouroboros.Consensus.Forecast | |
Exception HardForkEncoderException | |
Exception PastHorizonException | |
Defined in Ouroboros.Consensus.HardFork.History.Qry | |
Exception BlockFetchServerException | |
Exception ChainSyncClientException | |
Exception HistoricityException | |
Exception HeaderArrivalException | |
Exception PeerSentAnInvalidBlockException | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment Methods toException :: PeerSentAnInvalidBlockException -> SomeException # fromException :: SomeException -> Maybe PeerSentAnInvalidBlockException # displayException :: PeerSentAnInvalidBlockException -> String # backtraceDesired :: PeerSentAnInvalidBlockException -> Bool # | |
Exception ChunkAssertionFailure | |
Exception FuseBlownException | |
Defined in Ouroboros.Consensus.Util Methods toException :: FuseBlownException -> SomeException # fromException :: SomeException -> Maybe FuseBlownException # | |
Exception VersionError | |
Defined in Ouroboros.Consensus.Util.Versioned Methods toException :: VersionError -> SomeException # fromException :: SomeException -> Maybe VersionError # displayException :: VersionError -> String # backtraceDesired :: VersionError -> Bool # | |
Exception ShelleyReapplyException | |
Exception TxSubmissionProtocolError | |
Exception KeepAliveProtocolFailure | |
Exception WriteBitsException | |
Defined in PlutusCore.Bitwise Methods toException :: WriteBitsException -> SomeException # fromException :: SomeException -> Maybe WriteBitsException # displayException :: WriteBitsException -> String # backtraceDesired :: WriteBitsException -> Bool # | |
Exception FreeVariableError | |
Defined in PlutusCore.DeBruijn.Internal Methods toException :: FreeVariableError -> SomeException # fromException :: SomeException -> Maybe FreeVariableError # | |
Exception ApplyProgramError | |
Defined in PlutusCore.Error Methods toException :: ApplyProgramError -> SomeException # fromException :: SomeException -> Maybe ApplyProgramError # | |
Exception CostModelApplyError | |
Exception BuiltinErrorCall | |
Defined in PlutusCore.Examples.Builtins Methods toException :: BuiltinErrorCall -> SomeException # fromException :: SomeException -> Maybe BuiltinErrorCall # | |
Exception IndicesLengthsMismatchException | |
Defined in PlutusCore.StdLib.Type Methods toException :: IndicesLengthsMismatchException -> SomeException # fromException :: SomeException -> Maybe IndicesLengthsMismatchException # displayException :: IndicesLengthsMismatchException -> String # backtraceDesired :: IndicesLengthsMismatchException -> Bool # | |
Exception ScriptDecodeError | |
Defined in PlutusLedgerApi.Common.SerialisedScript Methods toException :: ScriptDecodeError -> SomeException # fromException :: SomeException -> Maybe ScriptDecodeError # | |
Exception LedgerBytesError | |
Defined in PlutusLedgerApi.V1.Bytes Methods toException :: LedgerBytesError -> SomeException # fromException :: SomeException -> Maybe LedgerBytesError # | |
Exception ImpossibleDeserialisationFailure | |
Exception ConstraintViolation | |
Defined in Database.PostgreSQL.Simple.Errors | |
Exception ResultError | |
Defined in Database.PostgreSQL.Simple.FromField Methods toException :: ResultError -> SomeException # fromException :: SomeException -> Maybe ResultError # displayException :: ResultError -> String # backtraceDesired :: ResultError -> Bool # | |
Exception FormatError | |
Defined in Database.PostgreSQL.Simple.Internal Methods toException :: FormatError -> SomeException # fromException :: SomeException -> Maybe FormatError # displayException :: FormatError -> String # backtraceDesired :: FormatError -> Bool # | |
Exception QueryError | |
Defined in Database.PostgreSQL.Simple.Internal Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String # backtraceDesired :: QueryError -> Bool # | |
Exception SomePostgreSqlException | |
Exception SqlError | |
Defined in Database.PostgreSQL.Simple.Internal Methods toException :: SqlError -> SomeException # fromException :: SomeException -> Maybe SqlError # displayException :: SqlError -> String # backtraceDesired :: SqlError -> Bool # | |
Exception ManyErrors | |
Defined in Database.PostgreSQL.Simple.Ok Methods toException :: ManyErrors -> SomeException # fromException :: SomeException -> Maybe ManyErrors # displayException :: ManyErrors -> String # backtraceDesired :: ManyErrors -> Bool # | |
Exception RegistryClosedException | |
Defined in Control.ResourceRegistry | |
Exception ResourceRegistryThreadException | |
Defined in Control.ResourceRegistry | |
Exception TempRegistryException | |
Defined in Control.ResourceRegistry | |
Exception InvalidAccess | |
Defined in Control.Monad.Trans.Resource.Internal Methods toException :: InvalidAccess -> SomeException # fromException :: SomeException -> Maybe InvalidAccess # displayException :: InvalidAccess -> String # backtraceDesired :: InvalidAccess -> Bool # | |
Exception ResourceCleanupException | |
Exception InvalidBaseUrlException | |
Defined in Servant.Client.Core.BaseUrl | |
Exception ClientError | |
Defined in Servant.Client.Core.ClientError Methods toException :: ClientError -> SomeException # fromException :: SomeException -> Maybe ClientError # displayException :: ClientError -> String # backtraceDesired :: ClientError -> Bool # | |
Exception AssertionException | |
Defined in Control.State.Transition.Extended Methods toException :: AssertionException -> SomeException # fromException :: SomeException -> Maybe AssertionException # | |
Exception ResourceError | |
Defined in Test.Tasty.Core Methods toException :: ResourceError -> SomeException # fromException :: SomeException -> Maybe ResourceError # displayException :: ResourceError -> String # backtraceDesired :: ResourceError -> Bool # | |
Exception HUnitFailure | |
Defined in Test.Tasty.HUnit.Orig Methods toException :: HUnitFailure -> SomeException # fromException :: SomeException -> Maybe HUnitFailure # displayException :: HUnitFailure -> String # backtraceDesired :: HUnitFailure -> Bool # | |
Exception UnicodeException | |
Defined in Data.Text.Encoding.Error Methods toException :: UnicodeException -> SomeException # fromException :: SomeException -> Maybe UnicodeException # | |
Exception ConcException | |
Defined in UnliftIO.Internals.Async Methods toException :: ConcException -> SomeException # fromException :: SomeException -> Maybe ConcException # displayException :: ConcException -> String # backtraceDesired :: ConcException -> Bool # | |
Exception PongTimeout | |
Defined in Network.WebSockets.Connection.PingPong Methods toException :: PongTimeout -> SomeException # fromException :: SomeException -> Maybe PongTimeout # displayException :: PongTimeout -> String # backtraceDesired :: PongTimeout -> Bool # | |
Exception ConnectionException | |
Defined in Network.WebSockets.Types | |
Exception DecompressError | |
Defined in Codec.Compression.Zlib.Internal Methods toException :: DecompressError -> SomeException # fromException :: SomeException -> Maybe DecompressError # displayException :: DecompressError -> String # backtraceDesired :: DecompressError -> Bool # | |
KnownNat csz => Exception (MnemonicException csz) | |
Defined in Cardano.Mnemonic Methods toException :: MnemonicException csz -> SomeException # fromException :: SomeException -> Maybe (MnemonicException csz) # displayException :: MnemonicException csz -> String # backtraceDesired :: MnemonicException csz -> Bool # | |
Exception a => Exception (ExceptionWithContext a) | |
Defined in GHC.Internal.Exception.Type Methods toException :: ExceptionWithContext a -> SomeException # fromException :: SomeException -> Maybe (ExceptionWithContext a) # displayException :: ExceptionWithContext a -> String # backtraceDesired :: ExceptionWithContext a -> Bool # | |
Exception e => Exception (NoBacktrace e) | |
Defined in GHC.Internal.Exception.Type Methods toException :: NoBacktrace e -> SomeException # fromException :: SomeException -> Maybe (NoBacktrace e) # displayException :: NoBacktrace e -> String # backtraceDesired :: NoBacktrace e -> Bool # | |
Typeable a => Exception (FieldException a) | |
Defined in Data.Data.Lens Methods toException :: FieldException a -> SomeException # fromException :: SomeException -> Maybe (FieldException a) # displayException :: FieldException a -> String # backtraceDesired :: FieldException a -> Bool # | |
(Typeable blk, Show (SomeSecond BlockQuery blk), Show (BlockNodeToClientVersion blk)) => Exception (QueryEncoderException blk) | |
Defined in Ouroboros.Consensus.Ledger.Query Methods toException :: QueryEncoderException blk -> SomeException # fromException :: SomeException -> Maybe (QueryEncoderException blk) # displayException :: QueryEncoderException blk -> String # backtraceDesired :: QueryEncoderException blk -> Bool # | |
(Typeable blk, StandardHash blk) => Exception (ChainDbError blk) | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API Methods toException :: ChainDbError blk -> SomeException # fromException :: SomeException -> Maybe (ChainDbError blk) # displayException :: ChainDbError blk -> String # backtraceDesired :: ChainDbError blk -> Bool # | |
(Typeable blk, StandardHash blk) => Exception (ChainDbFailure blk) | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API Methods toException :: ChainDbFailure blk -> SomeException # fromException :: SomeException -> Maybe (ChainDbFailure blk) # displayException :: ChainDbFailure blk -> String # backtraceDesired :: ChainDbFailure blk -> Bool # | |
(StandardHash blk, Typeable blk) => Exception (ImmutableDBError blk) | |
Defined in Ouroboros.Consensus.Storage.ImmutableDB.API Methods toException :: ImmutableDBError blk -> SomeException # fromException :: SomeException -> Maybe (ImmutableDBError blk) # displayException :: ImmutableDBError blk -> String # backtraceDesired :: ImmutableDBError blk -> Bool # | |
(StandardHash blk, Typeable blk) => Exception (VolatileDBError blk) | |
Defined in Ouroboros.Consensus.Storage.VolatileDB.API Methods toException :: VolatileDBError blk -> SomeException # fromException :: SomeException -> Maybe (VolatileDBError blk) # displayException :: VolatileDBError blk -> String # backtraceDesired :: VolatileDBError blk -> Bool # | |
(Typeable vNumber, Show vNumber) => Exception (HandshakeProtocolError vNumber) | |
Defined in Ouroboros.Network.Protocol.Handshake.Type Methods toException :: HandshakeProtocolError vNumber -> SomeException # fromException :: SomeException -> Maybe (HandshakeProtocolError vNumber) # displayException :: HandshakeProtocolError vNumber -> String # backtraceDesired :: HandshakeProtocolError vNumber -> Bool # | |
(Typeable vNumber, Show vNumber) => Exception (RefuseReason vNumber) | |
Defined in Ouroboros.Network.Protocol.Handshake.Type Methods toException :: RefuseReason vNumber -> SomeException # fromException :: SomeException -> Maybe (RefuseReason vNumber) # displayException :: RefuseReason vNumber -> String # backtraceDesired :: RefuseReason vNumber -> Bool # | |
Exception (UniqueError SrcSpan) | |
Defined in PlutusCore.Error Methods toException :: UniqueError SrcSpan -> SomeException # fromException :: SomeException -> Maybe (UniqueError SrcSpan) # displayException :: UniqueError SrcSpan -> String # backtraceDesired :: UniqueError SrcSpan -> Bool # | |
(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, Typeable s, Typeable e) => Exception (ParseError s e) | |
Defined in Text.Megaparsec.Error Methods toException :: ParseError s e -> SomeException # fromException :: SomeException -> Maybe (ParseError s e) # displayException :: ParseError s e -> String # backtraceDesired :: ParseError s e -> Bool # | |
(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, TraversableStream s, Typeable s, Typeable e) => Exception (ParseErrorBundle s e) | |
Defined in Text.Megaparsec.Error Methods toException :: ParseErrorBundle s e -> SomeException # fromException :: SomeException -> Maybe (ParseErrorBundle s e) # displayException :: ParseErrorBundle s e -> String # backtraceDesired :: ParseErrorBundle s e -> Bool # | |
(Typeable era, Typeable proto) => Exception (ShelleyEncoderException era proto) | |
Defined in Ouroboros.Consensus.Shelley.Node.Serialisation Methods toException :: ShelleyEncoderException era proto -> SomeException # fromException :: SomeException -> Maybe (ShelleyEncoderException era proto) # displayException :: ShelleyEncoderException era proto -> String # backtraceDesired :: ShelleyEncoderException era proto -> Bool # | |
(PrettyPlc cause, PrettyPlc err, Typeable cause, Typeable err) => Exception (ErrorWithCause err cause) | |
Defined in PlutusCore.Evaluation.ErrorWithCause Methods toException :: ErrorWithCause err cause -> SomeException # fromException :: SomeException -> Maybe (ErrorWithCause err cause) # displayException :: ErrorWithCause err cause -> String # backtraceDesired :: ErrorWithCause err cause -> Bool # | |
(ThrowableBuiltins uni fun, Pretty ann, Typeable ann) => Exception (Error uni fun ann) | |
Defined in PlutusIR.Error Methods toException :: Error uni fun ann -> SomeException # fromException :: SomeException -> Maybe (Error uni fun ann) # displayException :: Error uni fun ann -> String # backtraceDesired :: Error uni fun ann -> Bool # | |
(Reifies s (SomeException -> Maybe a), Typeable a, Typeable s, Typeable m) => Exception (Handling a s m) | |
Defined in Control.Lens.Internal.Exception Methods toException :: Handling a s m -> SomeException # fromException :: SomeException -> Maybe (Handling a s m) # displayException :: Handling a s m -> String # backtraceDesired :: Handling a s m -> Bool # |
sortBy :: (a -> a -> Ordering) -> [a] -> [a] #
The sortBy
function is the non-overloaded version of sort
.
The argument must be finite.
The supplied comparison relation is supposed to be reflexive and antisymmetric,
otherwise, e. g., for _ _ -> GT
, the ordered list simply does not exist.
The relation is also expected to be transitive: if it is not then sortBy
might fail to find an ordered permutation, even if it exists.
Examples
>>>
sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
Arguments
:: Exception e | |
=> IO a | The computation to run |
-> (e -> IO a) | Handler to invoke if an exception is raised |
-> IO a |
This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:
catch (readFile f) (\e -> do let err = show (e :: IOException) hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err) return "")
Note that we have to give a type signature to e
, or the program
will not typecheck as the type is ambiguous. While it is possible
to catch exceptions of any type, see the section "Catching all
exceptions" (in Control.Exception) for an explanation of the problems with doing so.
For catching exceptions in pure (non-IO
) expressions, see the
function evaluate
.
Note that due to Haskell's unspecified evaluation order, an
expression may throw one of several possible exceptions: consider
the expression (error "urk") + (1 `div` 0)
. Does
the expression throw
ErrorCall "urk"
, or DivideByZero
?
The answer is "it might throw either"; the choice is
non-deterministic. If you are catching any type of exception then you
might catch either. If you are calling catch
with type
IO Int -> (ArithException -> IO Int) -> IO Int
then the handler may
get run with DivideByZero
as an argument, or an ErrorCall "urk"
exception may be propagated further up. If you call it again, you
might get the opposite behaviour. This is ok, because catch
is an
IO
computation.
throwIO :: (HasCallStack, Exception e) => e -> IO a #
A variant of throw
that can only be used within the IO
monad.
Although throwIO
has a type that is an instance of the type of throw
, the
two functions are subtly different:
throw e `seq` () ===> throw e throwIO e `seq` () ===> ()
The first example will cause the exception e
to be raised,
whereas the second one won't. In fact, throwIO
will only cause
an exception to be raised when it is used within the IO
monad.
The throwIO
variant should be used in preference to throw
to
raise an exception within the IO
monad because it guarantees
ordering with respect to other operations, whereas throw
does not. We say that throwIO
throws *precise* exceptions and
throw
, error
, etc. all throw *imprecise* exceptions.
For example
throw e + error "boom" ===> error "boom" throw e + error "boom" ===> throw e
are both valid reductions and the compiler may pick any (loop, even), whereas
throwIO e >> error "boom" ===> throwIO e
will always throw e
when executed.
See also the GHC wiki page on precise exceptions for a more technical introduction to how GHC optimises around precise vs. imprecise exceptions.
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm] == do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
Examples
>>>
do x <- getLine
unless (x == "hi") (putStrLn "hi!") comingupwithexamplesisdifficult hi!
>>>
unless (pi > exp 1) Nothing
Just ()
A set of values a
.
Instances
ToJSON1 Set | |||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Set a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Set a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding # liftOmitField :: (a -> Bool) -> Set a -> Bool # | |||||
Eq1 Set | Since: containers-0.5.9 | ||||
Ord1 Set | Since: containers-0.5.9 | ||||
Defined in Data.Set.Internal | |||||
Show1 Set | Since: containers-0.5.9 | ||||
Foldable Set | Folds in order of increasing key. | ||||
Defined in Data.Set.Internal Methods fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |||||
Hashable1 Set | Since: hashable-1.3.4.0 | ||||
Defined in Data.Hashable.Class | |||||
Condense1 Set | |||||
Defined in Ouroboros.Consensus.Util.Condense Methods liftCondense :: (a -> String) -> Set a -> String # | |||||
Ord k => Indexable k (Set k) | |||||
Lift a => Lift (Set a :: Type) | Since: containers-0.6.6 | ||||
Structured k => Structured (Set k) | |||||
Defined in Distribution.Utils.Structured | |||||
(Ord a, FromJSON a) => FromJSON (Set a) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON a => ToJSON (Set a) | |||||
(Ord a, FromCBOR a) => FromCBOR (Set a) | |||||
(Ord a, ToCBOR a) => ToCBOR (Set a) | |||||
(Ord a, DecCBOR a) => DecCBOR (Set a) | |||||
(Ord k, DecCBOR k) => DecShareCBOR (Set k) | |||||
(Ord a, EncCBOR a) => EncCBOR (Set a) | |||||
Default (Set v) | |||||
Defined in Data.Default.Internal | |||||
NFData a => NFData (Set a) | |||||
Defined in Data.Set.Internal | |||||
Ord a => Monoid (Set a) | |||||
Ord a => Semigroup (Set a) | Since: containers-0.5.7 | ||||
(Data a, Ord a) => Data (Set a) | |||||
Defined in Data.Set.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |||||
Ord a => IsList (Set a) | Since: containers-0.5.6.2 | ||||
(Read a, Ord a) => Read (Set a) | |||||
Show a => Show (Set a) | |||||
Eq a => Eq (Set a) | |||||
Ord a => Ord (Set a) | |||||
Hashable v => Hashable (Set v) | Since: hashable-1.3.4.0 | ||||
Defined in Data.Hashable.Class | |||||
Ord k => At (Set k) | |||||
Ord a => Contains (Set a) | |||||
Ord k => Ixed (Set k) | |||||
Defined in Control.Lens.At | |||||
AsEmpty (Set a) | |||||
Defined in Control.Lens.Empty | |||||
Ord a => Wrapped (Set a) | |||||
Ord element => IsSet (Set element) | |||||
Defined in Data.Containers Methods insertSet :: Element (Set element) -> Set element -> Set element # deleteSet :: Element (Set element) -> Set element -> Set element # singletonSet :: Element (Set element) -> Set element # setFromList :: [Element (Set element)] -> Set element # setToList :: Set element -> [Element (Set element)] # filterSet :: (Element (Set element) -> Bool) -> Set element -> Set element # | |||||
Ord element => SetContainer (Set element) | |||||
Defined in Data.Containers Associated Types
Methods member :: ContainerKey (Set element) -> Set element -> Bool # notMember :: ContainerKey (Set element) -> Set element -> Bool # union :: Set element -> Set element -> Set element # unions :: (MonoFoldable mono, Element mono ~ Set element) => mono -> Set element # difference :: Set element -> Set element -> Set element # intersection :: Set element -> Set element -> Set element # keys :: Set element -> [ContainerKey (Set element)] # | |||||
Ord v => GrowingAppend (Set v) | |||||
Defined in Data.MonoTraversable | |||||
Ord e => MonoFoldable (Set e) | |||||
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Set e) -> m) -> Set e -> m # ofoldr :: (Element (Set e) -> b -> b) -> b -> Set e -> b # ofoldl' :: (a -> Element (Set e) -> a) -> a -> Set e -> a # otoList :: Set e -> [Element (Set e)] # oall :: (Element (Set e) -> Bool) -> Set e -> Bool # oany :: (Element (Set e) -> Bool) -> Set e -> Bool # ocompareLength :: Integral i => Set e -> i -> Ordering # otraverse_ :: Applicative f => (Element (Set e) -> f b) -> Set e -> f () # ofor_ :: Applicative f => Set e -> (Element (Set e) -> f b) -> f () # omapM_ :: Applicative m => (Element (Set e) -> m ()) -> Set e -> m () # oforM_ :: Applicative m => Set e -> (Element (Set e) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Set e) -> m a) -> a -> Set e -> m a # ofoldMap1Ex :: Semigroup m => (Element (Set e) -> m) -> Set e -> m # ofoldr1Ex :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # ofoldl1Ex' :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # headEx :: Set e -> Element (Set e) # lastEx :: Set e -> Element (Set e) # unsafeHead :: Set e -> Element (Set e) # unsafeLast :: Set e -> Element (Set e) # maximumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # minimumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # | |||||
MonoPointed (Set a) | |||||
Ord a => DistributiveGCDMonoid (Set a) | |||||
Defined in Data.Monoid.GCD | |||||
Ord a => GCDMonoid (Set a) | O(m*log(n/m + 1)), m <= n | ||||
Ord a => LeftDistributiveGCDMonoid (Set a) | |||||
Defined in Data.Monoid.GCD | |||||
Ord a => LeftGCDMonoid (Set a) | O(m*log(n/m + 1)), m <= n | ||||
Defined in Data.Monoid.GCD | |||||
Ord a => RightDistributiveGCDMonoid (Set a) | |||||
Defined in Data.Monoid.GCD | |||||
Ord a => RightGCDMonoid (Set a) | O(m*log(n/m + 1)), m <= n | ||||
Defined in Data.Monoid.GCD | |||||
Ord a => MonoidNull (Set a) | |||||
Defined in Data.Monoid.Null | |||||
Ord a => PositiveMonoid (Set a) | |||||
Defined in Data.Monoid.Null | |||||
Ord a => LeftReductive (Set a) | O(m*log(nm + 1)), m <= n/ | ||||
Defined in Data.Semigroup.Cancellative | |||||
Ord a => Reductive (Set a) | O(m*log(nm + 1)), m <= n/ | ||||
Ord a => RightReductive (Set a) | O(m*log(nm + 1)), m <= n/ | ||||
Defined in Data.Semigroup.Cancellative | |||||
NoThunks a => NoThunks (Set a) | |||||
AesonDefaultValue (Set a) | |||||
Defined in Data.OpenApi.Internal.AesonUtils Methods defaultValue :: Maybe (Set a) # | |||||
ToParamSchema a => ToParamSchema (Set a) | |||||
Defined in Data.OpenApi.Internal.ParamSchema Methods toParamSchema :: Proxy (Set a) -> Schema # | |||||
ToSchema a => ToSchema (Set a) | |||||
Defined in Data.OpenApi.Internal.Schema Methods declareNamedSchema :: Proxy (Set a) -> Declare (Definitions Schema) NamedSchema # | |||||
Ord a => SwaggerMonoid (Set a) | |||||
Defined in Data.OpenApi.Internal.Utils | |||||
Ord k => At (Set k) | |||||
Ord a => Contains (Set a) | |||||
Ord k => Ixed (Set k) | |||||
Condense a => Condense (Set a) | |||||
Defined in Ouroboros.Consensus.Util.Condense | |||||
(Ord a, Serialise a) => Serialise (Set a) | Since: serialise-0.2.0.0 | ||||
AesonDefaultValue (Set a) | |||||
Defined in Data.Swagger.Internal.AesonUtils Methods defaultValue :: Maybe (Set a) # | |||||
ToParamSchema a => ToParamSchema (Set a) | |||||
Defined in Data.Swagger.Internal.ParamSchema Methods toParamSchema :: forall (t :: SwaggerKind Type). Proxy (Set a) -> ParamSchema t # | |||||
ToSchema a => ToSchema (Set a) | |||||
Defined in Data.Swagger.Internal.Schema Methods declareNamedSchema :: Proxy (Set a) -> Declare (Definitions Schema) NamedSchema # | |||||
Ord a => SwaggerMonoid (Set a) | |||||
Defined in Data.Swagger.Internal.Utils | |||||
(t ~ Set a', Ord a) => Rewrapped (Set a) t | |||||
Defined in Control.Lens.Wrapped | |||||
type Share (Set k) | |||||
type Item (Set a) | |||||
Defined in Data.Set.Internal | |||||
type Index (Set a) | |||||
Defined in Control.Lens.At | |||||
type IxValue (Set k) | |||||
Defined in Control.Lens.At | |||||
type Unwrapped (Set a) | |||||
Defined in Control.Lens.Wrapped | |||||
type ContainerKey (Set element) | |||||
Defined in Data.Containers | |||||
type Element (Set e) | |||||
Defined in Data.MonoTraversable | |||||
type Index (Set a) | |||||
Defined in Optics.At.Core | |||||
type IxKind (Set k) | |||||
Defined in Optics.At.Core | |||||
type IxValue (Set k) | |||||
Defined in Optics.At.Core |
A Map from keys k
to values a
.
The Semigroup
operation for Map
is union
, which prefers
values from the left operand. If m1
maps a key k
to a value
a1
, and m2
maps the same key to a different value a2
, then
their union m1 <> m2
maps k
to a1
.
Instances
Bifoldable Map | Since: containers-0.6.3.1 | ||||
Eq2 Map | Since: containers-0.5.9 | ||||
Ord2 Map | Since: containers-0.5.9 | ||||
Defined in Data.Map.Internal | |||||
Show2 Map | Since: containers-0.5.9 | ||||
Hashable2 Map | Since: hashable-1.3.4.0 | ||||
Defined in Data.Hashable.Class | |||||
BiPolyMap Map | |||||
Defined in Data.Containers Associated Types
Methods mapKeysWith :: (BPMKeyConstraint Map k1, BPMKeyConstraint Map k2) => (v -> v -> v) -> (k1 -> k2) -> Map k1 v -> Map k2 v # | |||||
FoldableWithIndex k (Map k) | |||||
FunctorWithIndex k (Map k) | |||||
TraversableWithIndex k (Map k) | |||||
Ord k => TraverseMax k (Map k) | |||||
Defined in Control.Lens.Traversal Methods traverseMax :: IndexedTraversal' k (Map k v) v # | |||||
Ord k => TraverseMin k (Map k) | |||||
Defined in Control.Lens.Traversal Methods traverseMin :: IndexedTraversal' k (Map k v) v # | |||||
FilterableWithIndex k (Map k) | |||||
WitherableWithIndex k (Map k) | |||||
Ord k => Indexable k (Map k v) | |||||
(Lift k, Lift a) => Lift (Map k a :: Type) | Since: containers-0.6.6 | ||||
(FromJSONKey k, Ord k) => FromJSON1 (Map k) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSONKey k => ToJSON1 (Map k) | |||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Map k a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding # liftOmitField :: (a -> Bool) -> Map k a -> Bool # | |||||
Eq k => Eq1 (Map k) | Since: containers-0.5.9 | ||||
Ord k => Ord1 (Map k) | Since: containers-0.5.9 | ||||
Defined in Data.Map.Internal | |||||
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 | ||||
Defined in Data.Map.Internal | |||||
Show k => Show1 (Map k) | Since: containers-0.5.9 | ||||
Functor (Map k) | |||||
Foldable (Map k) | Folds in order of increasing key. | ||||
Defined in Data.Map.Internal Methods fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |||||
Traversable (Map k) | Traverses in order of increasing key. | ||||
Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 | ||||
Defined in Data.Hashable.Class | |||||
Ord key => PolyMap (Map key) | This instance uses the functions from Data.Map.Strict. | ||||
Defined in Data.Containers Methods differenceMap :: Map key value1 -> Map key value2 -> Map key value1 # intersectionMap :: Map key value1 -> Map key value2 -> Map key value1 # intersectionWithMap :: (value1 -> value2 -> value3) -> Map key value1 -> Map key value2 -> Map key value3 # | |||||
Filterable (Map k) | |||||
Witherable (Map k) | |||||
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Map k a -> f (Map k b) # witherM :: Monad m => (a -> m (Maybe b)) -> Map k a -> m (Map k b) # filterA :: Applicative f => (a -> f Bool) -> Map k a -> f (Map k a) # witherMap :: Applicative m => (Map k b -> r) -> (a -> m (Maybe b)) -> Map k a -> m r # | |||||
(Structured k, Structured v) => Structured (Map k v) | |||||
Defined in Distribution.Utils.Structured | |||||
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |||||
(Ord k, FromCBOR k, FromCBOR v) => FromCBOR (Map k v) | |||||
(Ord k, ToCBOR k, ToCBOR v) => ToCBOR (Map k v) | |||||
(Ord k, DecCBOR k, DecCBOR v) => DecCBOR (Map k v) | |||||
(Ord k, DecCBOR k, DecCBOR v) => DecShareCBOR (Map k v) | |||||
(Ord k, EncCBOR k, EncCBOR v) => EncCBOR (Map k v) | |||||
(Ord a, ToPlutusData a, ToPlutusData b) => ToPlutusData (Map a b) | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData | |||||
(FromField a, FromField b, Ord a) => FromNamedRecord (Map a b) | |||||
Defined in Data.Csv.Conversion Methods parseNamedRecord :: NamedRecord -> Parser (Map a b) # | |||||
(ToField a, ToField b, Ord a) => ToNamedRecord (Map a b) | |||||
Defined in Data.Csv.Conversion Methods toNamedRecord :: Map a b -> NamedRecord # | |||||
Default (Map k v) | |||||
Defined in Data.Default.Internal | |||||
(NFData k, NFData a) => NFData (Map k a) | |||||
Defined in Data.Map.Internal | |||||
Ord k => Monoid (Map k v) | |||||
Ord k => Semigroup (Map k v) | |||||
(Data k, Data a, Ord k) => Data (Map k a) | |||||
Defined in Data.Map.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |||||
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 | ||||
(Ord k, Read k, Read e) => Read (Map k e) | |||||
(Show k, Show a) => Show (Map k a) | |||||
(Eq k, Eq a) => Eq (Map k a) | |||||
(Ord k, Ord v) => Ord (Map k v) | |||||
(Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 | ||||
Defined in Data.Hashable.Class | |||||
(Ord k, FromFormKey k, FromHttpApiData v) => FromForm (Map k [v]) | |||||
(ToFormKey k, ToHttpApiData v) => ToForm (Map k [v]) | |||||
Defined in Web.Internal.FormUrlEncoded | |||||
Ord k => At (Map k a) | |||||
Ord k => Ixed (Map k a) | |||||
Defined in Control.Lens.At | |||||
AsEmpty (Map k a) | |||||
Defined in Control.Lens.Empty | |||||
Ord k => Wrapped (Map k a) | |||||
Ord k => HasKeysSet (Map k v) | |||||
Ord key => IsMap (Map key value) | This instance uses the functions from Data.Map.Strict. | ||||
Defined in Data.Containers Associated Types
Methods lookup :: ContainerKey (Map key value) -> Map key value -> Maybe (MapValue (Map key value)) # insertMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # deleteMap :: ContainerKey (Map key value) -> Map key value -> Map key value # singletonMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value # mapFromList :: [(ContainerKey (Map key value), MapValue (Map key value))] -> Map key value # mapToList :: Map key value -> [(ContainerKey (Map key value), MapValue (Map key value))] # findWithDefault :: MapValue (Map key value) -> ContainerKey (Map key value) -> Map key value -> MapValue (Map key value) # insertWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # insertWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # insertLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) # adjustMap :: (MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value # adjustWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateMap :: (MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) # alterMap :: (Maybe (MapValue (Map key value)) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # unionWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value # unionWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value # unionsWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> [Map key value] -> Map key value # mapWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value # omapKeysWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> (ContainerKey (Map key value) -> ContainerKey (Map key value)) -> Map key value -> Map key value # filterMap :: (MapValue (Map key value) -> Bool) -> Map key value -> Map key value # filterWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Bool) -> Map key value -> Map key value # | |||||
Ord k => SetContainer (Map k v) | This instance uses the functions from Data.Map.Strict. | ||||
Defined in Data.Containers Associated Types
Methods member :: ContainerKey (Map k v) -> Map k v -> Bool # notMember :: ContainerKey (Map k v) -> Map k v -> Bool # union :: Map k v -> Map k v -> Map k v # unions :: (MonoFoldable mono, Element mono ~ Map k v) => mono -> Map k v # difference :: Map k v -> Map k v -> Map k v # intersection :: Map k v -> Map k v -> Map k v # keys :: Map k v -> [ContainerKey (Map k v)] # | |||||
Ord k => GrowingAppend (Map k v) | |||||
Defined in Data.MonoTraversable | |||||
MonoFoldable (Map k v) | |||||
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b # ofoldl' :: (a -> Element (Map k v) -> a) -> a -> Map k v -> a # otoList :: Map k v -> [Element (Map k v)] # oall :: (Element (Map k v) -> Bool) -> Map k v -> Bool # oany :: (Element (Map k v) -> Bool) -> Map k v -> Bool # olength64 :: Map k v -> Int64 # ocompareLength :: Integral i => Map k v -> i -> Ordering # otraverse_ :: Applicative f => (Element (Map k v) -> f b) -> Map k v -> f () # ofor_ :: Applicative f => Map k v -> (Element (Map k v) -> f b) -> f () # omapM_ :: Applicative m => (Element (Map k v) -> m ()) -> Map k v -> m () # oforM_ :: Applicative m => Map k v -> (Element (Map k v) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Map k v) -> m a) -> a -> Map k v -> m a # ofoldMap1Ex :: Semigroup m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr1Ex :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # ofoldl1Ex' :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # headEx :: Map k v -> Element (Map k v) # lastEx :: Map k v -> Element (Map k v) # unsafeHead :: Map k v -> Element (Map k v) # unsafeLast :: Map k v -> Element (Map k v) # maximumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # minimumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # | |||||
MonoFunctor (Map k v) | |||||
MonoTraversable (Map k v) | |||||
(Ord k, Eq a) => LeftGCDMonoid (Map k a) | O(m+n) | ||||
Defined in Data.Monoid.GCD | |||||
Ord k => MonoidNull (Map k v) | |||||
Defined in Data.Monoid.Null | |||||
Ord k => PositiveMonoid (Map k v) | |||||
Defined in Data.Monoid.Null | |||||
(Ord k, Eq a) => LeftReductive (Map k a) | O(m+n) | ||||
Defined in Data.Semigroup.Cancellative | |||||
(Ord k, Eq a) => RightReductive (Map k a) | O(m+n) | ||||
Defined in Data.Semigroup.Cancellative | |||||
(NoThunks k, NoThunks v) => NoThunks (Map k v) | |||||
(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (Map k v) | |||||
Defined in Data.OpenApi.Internal.Schema Methods declareNamedSchema :: Proxy (Map k v) -> Declare (Definitions Schema) NamedSchema # | |||||
Ord k => SwaggerMonoid (Map k v) | |||||
Defined in Data.OpenApi.Internal.Utils | |||||
Ord k => At (Map k a) | |||||
Ord k => Ixed (Map k a) | |||||
(Condense k, Condense a) => Condense (Map k a) | |||||
Defined in Ouroboros.Consensus.Util.Condense | |||||
(Ord k, Serialise k, Serialise v) => Serialise (Map k v) | Since: serialise-0.2.0.0 | ||||
FromHttpApiData a => FromDeepQuery (Map Text a) | |||||
Defined in Servant.API.QueryString | |||||
(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (Map k v) | |||||
Defined in Data.Swagger.Internal.Schema Methods declareNamedSchema :: Proxy (Map k v) -> Declare (Definitions Schema) NamedSchema # | |||||
Ord k => SwaggerMonoid (Map k v) | |||||
Defined in Data.Swagger.Internal.Utils | |||||
(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t | |||||
Defined in Control.Lens.Wrapped | |||||
Ord k => Rewrapped (Map k a) (MonoidalMap k a) | |||||
Defined in Data.Map.Monoidal | |||||
Ord k => Rewrapped (MonoidalMap k a) (Map k a) | |||||
Defined in Data.Map.Monoidal | |||||
Newtype (MonoidalMap k a) (Map k a) | |||||
Defined in Data.Map.Monoidal | |||||
c ~ d => Each (Map c a) (Map d b) a b |
| ||||
type BPMKeyConstraint Map key | |||||
Defined in Data.Containers | |||||
type Share (Map k v) | |||||
type Item (Map k v) | |||||
Defined in Data.Map.Internal | |||||
type Index (Map k a) | |||||
Defined in Control.Lens.At | |||||
type IxValue (Map k a) | |||||
Defined in Control.Lens.At | |||||
type Unwrapped (Map k a) | |||||
Defined in Control.Lens.Wrapped | |||||
type ContainerKey (Map k v) | |||||
Defined in Data.Containers | |||||
type KeySet (Map k v) | |||||
Defined in Data.Containers | |||||
type MapValue (Map key value) | |||||
Defined in Data.Containers | |||||
type Element (Map k v) | |||||
Defined in Data.MonoTraversable | |||||
type Index (Map k a) | |||||
Defined in Optics.At.Core | |||||
type IxKind (Map k a) | |||||
Defined in Optics.At.Core | |||||
type IxValue (Map k a) | |||||
Defined in Optics.At.Core |
(&) :: a -> (a -> b) -> b infixl 1 #
&
is a reverse application operator. This provides notational
convenience. Its precedence is one higher than that of the forward
application operator $
, which allows &
to be nested in $
.
This is a version of
, where flip
id
id
is specialized from a -> a
to (a -> b) -> (a -> b)
which by the associativity of (->)
is (a -> b) -> a -> b
.
flipping this yields a -> (a -> b) -> b
which is the type signature of &
Examples
>>>
5 & (+1) & show
"6"
>>>
sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
3.1406380562059946
@since base-4.8.0.0
coerce :: Coercible a b => a -> b #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
When used in conversions involving a newtype wrapper, make sure the newtype constructor is in scope.
This function is representation-polymorphic, but the
RuntimeRep
type argument is marked as Inferred
, meaning
that it is not available for visible type application. This means
the typechecker will accept
.coerce
@Int
@Age 42
Examples
>>>
newtype TTL = TTL Int deriving (Eq, Ord, Show)
>>>
newtype Age = Age Int deriving (Eq, Ord, Show)
>>>
coerce (Age 42) :: TTL
TTL 42>>>
coerce (+ (1 :: Int)) (Age 42) :: TTL
TTL 43>>>
coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
[TTL 43,TTL 25]
type Constraint = CONSTRAINT LiftedRep #
The kind of lifted constraints
A space efficient, packed, unboxed Unicode text type.
Instances
Structured Text | |||||||||||||
Defined in Distribution.Utils.Structured | |||||||||||||
FromJSON Text | |||||||||||||
Defined in Data.Aeson.Types.FromJSON | |||||||||||||
FromJSONKey Text | |||||||||||||
Defined in Data.Aeson.Types.FromJSON | |||||||||||||
ToJSON Text | |||||||||||||
ToJSONKey Text | |||||||||||||
Defined in Data.Aeson.Types.ToJSON | |||||||||||||
Chunk Text | |||||||||||||
Defined in Data.Attoparsec.Internal.Types Associated Types
| |||||||||||||
FromCBOR Text | |||||||||||||
ToCBOR Text | |||||||||||||
DecCBOR Text | |||||||||||||
EncCBOR Text | |||||||||||||
FoldCase Text | |||||||||||||
Defined in Data.CaseInsensitive.Internal | |||||||||||||
FromField Text | Assumes UTF-8 encoding. Fails on invalid byte sequences. | ||||||||||||
Defined in Data.Csv.Conversion Methods parseField :: Field -> Parser Text # | |||||||||||||
ToField Text | Uses UTF-8 encoding. | ||||||||||||
Defined in Data.Csv.Conversion | |||||||||||||
Hashable Text | |||||||||||||
Defined in Data.Hashable.Class | |||||||||||||
FromFormKey Text | |||||||||||||
Defined in Web.Internal.FormUrlEncoded | |||||||||||||
ToFormKey Text | |||||||||||||
Defined in Web.Internal.FormUrlEncoded | |||||||||||||
FromHttpApiData Text | |||||||||||||
Defined in Web.Internal.HttpApiData | |||||||||||||
ToHttpApiData Text | |||||||||||||
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Text -> Text # toEncodedUrlPiece :: Text -> Builder # toHeader :: Text -> ByteString # toQueryParam :: Text -> Text # toEncodedQueryParam :: Text -> Builder # | |||||||||||||
QueryKeyLike Text | |||||||||||||
Defined in Network.HTTP.Types.QueryLike Methods toQueryKey :: Text -> ByteString # | |||||||||||||
QueryValueLike Text | |||||||||||||
Defined in Network.HTTP.Types.QueryLike Methods toQueryValue :: Text -> Maybe ByteString # | |||||||||||||
HasPrivacyAnnotation Text | |||||||||||||
Defined in Cardano.BM.Data.Tracer Methods | |||||||||||||
HasSeverityAnnotation Text | |||||||||||||
Defined in Cardano.BM.Data.Tracer Methods getSeverityAnnotation :: Text -> Severity # | |||||||||||||
ToObject Text | |||||||||||||
Defined in Cardano.BM.Data.Tracer | |||||||||||||
Ixed Text | |||||||||||||
Defined in Control.Lens.At | |||||||||||||
AsEmpty Text | |||||||||||||
Defined in Control.Lens.Empty | |||||||||||||
Reversing Text | |||||||||||||
Defined in Control.Lens.Internal.Iso | |||||||||||||
Prefixed Text | |||||||||||||
Suffixed Text | |||||||||||||
IsText Text | |||||||||||||
AsJSON Text | |||||||||||||
AsNumber Text | |||||||||||||
AsValue Text | |||||||||||||
IsKey Text | |||||||||||||
Stream Text | |||||||||||||
Defined in Text.Megaparsec.Stream Associated Types
Methods tokenToChunk :: Proxy Text -> Token Text -> Tokens Text # tokensToChunk :: Proxy Text -> [Token Text] -> Tokens Text # chunkToTokens :: Proxy Text -> Tokens Text -> [Token Text] # chunkLength :: Proxy Text -> Tokens Text -> Int # chunkEmpty :: Proxy Text -> Tokens Text -> Bool # take1_ :: Text -> Maybe (Token Text, Text) # takeN_ :: Int -> Text -> Maybe (Tokens Text, Text) # takeWhile_ :: (Token Text -> Bool) -> Text -> (Tokens Text, Text) # | |||||||||||||
TraversableStream Text | |||||||||||||
VisualStream Text | |||||||||||||
MemPack Text | |||||||||||||
MonoZip Text | |||||||||||||
GrowingAppend Text | |||||||||||||
Defined in Data.MonoTraversable | |||||||||||||
MonoFoldable Text | |||||||||||||
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element Text -> m) -> Text -> m # ofoldr :: (Element Text -> b -> b) -> b -> Text -> b # ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a # otoList :: Text -> [Element Text] # oall :: (Element Text -> Bool) -> Text -> Bool # oany :: (Element Text -> Bool) -> Text -> Bool # ocompareLength :: Integral i => Text -> i -> Ordering # otraverse_ :: Applicative f => (Element Text -> f b) -> Text -> f () # ofor_ :: Applicative f => Text -> (Element Text -> f b) -> f () # omapM_ :: Applicative m => (Element Text -> m ()) -> Text -> m () # oforM_ :: Applicative m => Text -> (Element Text -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element Text -> m a) -> a -> Text -> m a # ofoldMap1Ex :: Semigroup m => (Element Text -> m) -> Text -> m # ofoldr1Ex :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text # ofoldl1Ex' :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text # headEx :: Text -> Element Text # lastEx :: Text -> Element Text # unsafeHead :: Text -> Element Text # unsafeLast :: Text -> Element Text # maximumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text # minimumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text # | |||||||||||||
MonoFunctor Text | |||||||||||||
MonoPointed Text | |||||||||||||
MonoTraversable Text | |||||||||||||
IsSequence Text | |||||||||||||
Defined in Data.Sequences Methods fromList :: [Element Text] -> Text # lengthIndex :: Text -> Index Text # break :: (Element Text -> Bool) -> Text -> (Text, Text) # span :: (Element Text -> Bool) -> Text -> (Text, Text) # dropWhile :: (Element Text -> Bool) -> Text -> Text # takeWhile :: (Element Text -> Bool) -> Text -> Text # splitAt :: Index Text -> Text -> (Text, Text) # unsafeSplitAt :: Index Text -> Text -> (Text, Text) # take :: Index Text -> Text -> Text # unsafeTake :: Index Text -> Text -> Text # drop :: Index Text -> Text -> Text # unsafeDrop :: Index Text -> Text -> Text # dropEnd :: Index Text -> Text -> Text # partition :: (Element Text -> Bool) -> Text -> (Text, Text) # uncons :: Text -> Maybe (Element Text, Text) # unsnoc :: Text -> Maybe (Text, Element Text) # filter :: (Element Text -> Bool) -> Text -> Text # filterM :: Monad m => (Element Text -> m Bool) -> Text -> m Text # replicate :: Index Text -> Element Text -> Text # replicateM :: Monad m => Index Text -> m (Element Text) -> m Text # groupBy :: (Element Text -> Element Text -> Bool) -> Text -> [Text] # groupAllOn :: Eq b => (Element Text -> b) -> Text -> [Text] # subsequences :: Text -> [Text] # permutations :: Text -> [Text] # tailMay :: Text -> Maybe Text # initMay :: Text -> Maybe Text # unsafeTail :: Text -> Text # unsafeInit :: Text -> Text # index :: Text -> Index Text -> Maybe (Element Text) # indexEx :: Text -> Index Text -> Element Text # unsafeIndex :: Text -> Index Text -> Element Text # | |||||||||||||
SemiSequence Text | |||||||||||||
Defined in Data.Sequences | |||||||||||||
Textual Text | |||||||||||||
LeftDistributiveGCDMonoid Text | |||||||||||||
Defined in Data.Monoid.GCD | |||||||||||||
LeftGCDMonoid Text | O(prefixLength) | ||||||||||||
Defined in Data.Monoid.GCD | |||||||||||||
RightDistributiveGCDMonoid Text | |||||||||||||
Defined in Data.Monoid.GCD | |||||||||||||
RightGCDMonoid Text | O(suffixLength), except on GHCjs where it is O(m+n) Since: monoid-subclasses-1.0 | ||||||||||||
Defined in Data.Monoid.GCD | |||||||||||||
MonoidNull Text | |||||||||||||
Defined in Data.Monoid.Null | |||||||||||||
PositiveMonoid Text | |||||||||||||
Defined in Data.Monoid.Null | |||||||||||||
LeftCancellative Text | |||||||||||||
Defined in Data.Semigroup.Cancellative | |||||||||||||
LeftReductive Text | O(n) | ||||||||||||
Defined in Data.Semigroup.Cancellative | |||||||||||||
RightCancellative Text | |||||||||||||
Defined in Data.Semigroup.Cancellative | |||||||||||||
RightReductive Text | O(n) | ||||||||||||
Defined in Data.Semigroup.Cancellative | |||||||||||||
NoThunks Text | |||||||||||||
AesonDefaultValue Text | |||||||||||||
Defined in Data.OpenApi.Internal.AesonUtils Methods defaultValue :: Maybe Text # | |||||||||||||
ToParamSchema Text | |||||||||||||
Defined in Data.OpenApi.Internal.ParamSchema Methods toParamSchema :: Proxy Text -> Schema # | |||||||||||||
ToSchema Text | |||||||||||||
Defined in Data.OpenApi.Internal.Schema Methods declareNamedSchema :: Proxy Text -> Declare (Definitions Schema) NamedSchema # | |||||||||||||
SwaggerMonoid Text | |||||||||||||
Defined in Data.OpenApi.Internal.Utils | |||||||||||||
Condense Text | |||||||||||||
Defined in Ouroboros.Consensus.Util.Condense | |||||||||||||
ExMemoryUsage Text | |||||||||||||
Defined in PlutusCore.Evaluation.Machine.ExMemoryUsage Methods memoryUsage :: Text -> CostRose # | |||||||||||||
HasToBuiltin Text | |||||||||||||
Defined in PlutusTx.Builtins.HasBuiltin Associated Types
| |||||||||||||
FromField Text | name, text, "char", bpchar, varchar | ||||||||||||
Defined in Database.PostgreSQL.Simple.FromField Methods | |||||||||||||
ToField Text | |||||||||||||
Defined in Database.PostgreSQL.Simple.ToField | |||||||||||||
Pretty Text | Automatically converts all newlines to
Note that
Manually use | ||||||||||||
Defined in Prettyprinter.Internal | |||||||||||||
Serialise Text | Since: serialise-0.2.0.0 | ||||||||||||
AesonDefaultValue Text | |||||||||||||
Defined in Data.Swagger.Internal.AesonUtils Methods defaultValue :: Maybe Text # | |||||||||||||
ToParamSchema Text | |||||||||||||
Defined in Data.Swagger.Internal.ParamSchema Methods toParamSchema :: forall (t :: SwaggerKind Type). Proxy Text -> ParamSchema t # | |||||||||||||
ToSchema Text | |||||||||||||
Defined in Data.Swagger.Internal.Schema Methods declareNamedSchema :: Proxy Text -> Declare (Definitions Schema) NamedSchema # | |||||||||||||
SwaggerMonoid Text | |||||||||||||
Defined in Data.Swagger.Internal.Utils | |||||||||||||
WebSocketsData Text | |||||||||||||
Defined in Network.WebSockets.Types Methods fromDataMessage :: DataMessage -> Text # fromLazyByteString :: ByteString -> Text # toLazyByteString :: Text -> ByteString # | |||||||||||||
Pretty Text | |||||||||||||
Defined in Text.PrettyPrint.Annotated.WL | |||||||||||||
LazySequence Text Text | |||||||||||||
Utf8 Text ByteString | |||||||||||||
Defined in Data.Sequences | |||||||||||||
HasAuthorizationUrl OAuth2AuthorizationCodeFlow AuthorizationURL | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasAuthorizationUrl OAuth2ImplicitFlow AuthorizationURL | |||||||||||||
Defined in Data.OpenApi.Lens Methods authorizationUrl :: Lens' OAuth2ImplicitFlow AuthorizationURL # | |||||||||||||
HasDescription Response Text | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasName License Text | |||||||||||||
HasName Param Text | |||||||||||||
HasName Tag TagName | |||||||||||||
HasPropertyName Discriminator Text | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasTitle Info Text | |||||||||||||
HasTokenUrl OAuth2AuthorizationCodeFlow TokenURL | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasTokenUrl OAuth2ClientCredentialsFlow TokenURL | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasTokenUrl OAuth2PasswordFlow TokenURL | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasUrl Server Text | |||||||||||||
HasVersion Info Text | |||||||||||||
DefaultPrettyBy config Text | |||||||||||||
Defined in Text.PrettyBy.Internal Methods defaultPrettyBy :: config -> Text -> Doc ann # defaultPrettyListBy :: config -> [Text] -> Doc ann # | |||||||||||||
NonDefaultPrettyBy ConstConfig Text | |||||||||||||
Defined in PlutusCore.Pretty.PrettyConst Methods nonDefaultPrettyBy :: ConstConfig -> Text -> Doc ann # nonDefaultPrettyListBy :: ConstConfig -> [Text] -> Doc ann # | |||||||||||||
PrettyDefaultBy config Text => PrettyBy config Text | Automatically converts all newlines to
| ||||||||||||
Defined in Text.PrettyBy.Internal | |||||||||||||
StringConv ByteString Text | |||||||||||||
Defined in Data.String.Conv Methods strConv :: Leniency -> ByteString -> Text # | |||||||||||||
StringConv ByteString Text | |||||||||||||
Defined in Data.String.Conv Methods strConv :: Leniency -> ByteString -> Text # | |||||||||||||
StringConv Text ByteString | |||||||||||||
Defined in Data.String.Conv Methods strConv :: Leniency -> Text -> ByteString # | |||||||||||||
StringConv Text ByteString | |||||||||||||
Defined in Data.String.Conv Methods strConv :: Leniency -> Text -> ByteString # | |||||||||||||
StringConv Text Text | |||||||||||||
StringConv Text Text | |||||||||||||
StringConv Text String | |||||||||||||
StringConv Text Text | |||||||||||||
StringConv String Text | |||||||||||||
HasDescription Response Text | |||||||||||||
Defined in Data.Swagger.Lens Methods | |||||||||||||
HasName License Text | |||||||||||||
HasName Param Text | |||||||||||||
HasName Tag TagName | |||||||||||||
HasTitle Info Text | |||||||||||||
HasVersion Info Text | |||||||||||||
Transformable Text IO Text | |||||||||||||
Defined in Cardano.BM.Data.Tracer Methods trTransformer :: TracingVerbosity -> Trace IO Text -> Tracer IO Text # | |||||||||||||
Transformable Text IO String | |||||||||||||
Defined in Cardano.BM.Data.Tracer Methods trTransformer :: TracingVerbosity -> Trace IO Text -> Tracer IO String # | |||||||||||||
Transformable String IO Text | |||||||||||||
Defined in Cardano.BM.Data.Tracer Methods trTransformer :: TracingVerbosity -> Trace IO String -> Tracer IO Text # | |||||||||||||
KnownBuiltinTypeIn DefaultUni term Text => MakeKnownIn DefaultUni term Text | |||||||||||||
Defined in PlutusCore.Default.Universe Methods makeKnown :: Text -> BuiltinResult (HeadSpine term) # | |||||||||||||
KnownBuiltinTypeIn DefaultUni term Text => ReadKnownIn DefaultUni term Text | |||||||||||||
Defined in PlutusCore.Default.Universe Methods readKnown :: term -> ReadKnownM Text # | |||||||||||||
Contains DefaultUni Text | |||||||||||||
Defined in PlutusCore.Default.Universe Methods knownUni :: DefaultUni (Esc Text) # | |||||||||||||
MimeRender PlainText Text | fromStrict . TextS.encodeUtf8 | ||||||||||||
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> Text -> ByteString # | |||||||||||||
MimeUnrender PlainText Text | left show . TextS.decodeUtf8' . toStrict | ||||||||||||
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text # | |||||||||||||
Cons Text Text Char Char | |||||||||||||
Snoc Text Text Char Char | |||||||||||||
(a ~ Char, b ~ Char) => Each Text Text a b |
| ||||||||||||
KnownBuiltinTypeAst tyname DefaultUni Text => KnownTypeAst tyname DefaultUni Text | |||||||||||||
Defined in PlutusCore.Default.Universe Associated Types
Methods typeAst :: Type tyname DefaultUni () # | |||||||||||||
HasCallbacks Components (Definitions Callback) | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasDescription Example (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription ExternalDocs (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens Methods description :: Lens' ExternalDocs (Maybe Text) # | |||||||||||||
HasDescription Header (Maybe HeaderName) | |||||||||||||
Defined in Data.OpenApi.Lens Methods description :: Lens' Header (Maybe HeaderName) # | |||||||||||||
HasDescription Info (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription Link (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription Operation (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription Param (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription PathItem (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription RequestBody (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens Methods description :: Lens' RequestBody (Maybe Text) # | |||||||||||||
HasDescription Schema (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription SecurityScheme (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens Methods description :: Lens' SecurityScheme (Maybe Text) # | |||||||||||||
HasDescription Server (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasDescription Tag (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasEmail Contact (Maybe Text) | |||||||||||||
HasExamples Components (Definitions Example) | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasFormat Schema (Maybe Format) | |||||||||||||
HasSchema s Schema => HasFormat s (Maybe Format) | |||||||||||||
HasHeaders Components (Definitions Header) | |||||||||||||
Defined in Data.OpenApi.Lens Methods headers :: Lens' Components (Definitions Header) # | |||||||||||||
HasLinks Components (Definitions Link) | |||||||||||||
Defined in Data.OpenApi.Lens Methods links :: Lens' Components (Definitions Link) # | |||||||||||||
HasName Contact (Maybe Text) | |||||||||||||
HasName NamedSchema (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasName Xml (Maybe Text) | |||||||||||||
HasNamespace Xml (Maybe Text) | |||||||||||||
HasOperationId Link (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasOperationId Operation (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasOperationRef Link (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasParameters Components (Definitions Param) | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasPattern Schema (Maybe Pattern) | |||||||||||||
HasSchema s Schema => HasPattern s (Maybe Text) | |||||||||||||
HasPrefix Xml (Maybe Text) | |||||||||||||
HasRequestBodies Components (Definitions RequestBody) | |||||||||||||
Defined in Data.OpenApi.Lens Methods requestBodies :: Lens' Components (Definitions RequestBody) # | |||||||||||||
HasRequired Schema [ParamName] | |||||||||||||
HasResponses Components (Definitions Response) | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasSchemas Components (Definitions Schema) | |||||||||||||
Defined in Data.OpenApi.Lens Methods schemas :: Lens' Components (Definitions Schema) # | |||||||||||||
HasSummary Example (Maybe Text) | |||||||||||||
HasSummary Operation (Maybe Text) | |||||||||||||
HasSummary PathItem (Maybe Text) | |||||||||||||
HasTags Operation (InsOrdHashSet TagName) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasTermsOfService Info (Maybe Text) | |||||||||||||
Defined in Data.OpenApi.Lens | |||||||||||||
HasTitle Schema (Maybe Text) | |||||||||||||
HasDefinitions Swagger (Definitions Schema) | |||||||||||||
Defined in Data.Swagger.Lens Methods | |||||||||||||
HasDescription ExternalDocs (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens Methods description :: Lens' ExternalDocs (Maybe Text) # | |||||||||||||
HasDescription Header (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDescription Info (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDescription Operation (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDescription Param (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDescription Schema (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDescription SecurityScheme (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens Methods description :: Lens' SecurityScheme (Maybe Text) # | |||||||||||||
HasDescription Tag (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasDiscriminator Schema (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasEmail Contact (Maybe Text) | |||||||||||||
HasParamSchema s (ParamSchema t) => HasFormat s (Maybe Format) | |||||||||||||
HasName Contact (Maybe Text) | |||||||||||||
HasName NamedSchema (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasName Xml (Maybe Text) | |||||||||||||
HasNamespace Xml (Maybe Text) | |||||||||||||
HasOperationId Operation (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasParameters Swagger (Definitions Param) | |||||||||||||
Defined in Data.Swagger.Lens Methods parameters :: Lens' Swagger (Definitions Param) # | |||||||||||||
HasParamSchema s (ParamSchema t) => HasPattern s (Maybe Text) | |||||||||||||
HasPrefix Xml (Maybe Text) | |||||||||||||
HasRequired Schema [ParamName] | |||||||||||||
HasResponses Swagger (Definitions Response) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasSummary Operation (Maybe Text) | |||||||||||||
HasTags Operation (InsOrdHashSet TagName) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasTermsOfService Info (Maybe Text) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasTitle Schema (Maybe Text) | |||||||||||||
HasCallbacks Operation (InsOrdHashMap Text (Referenced Callback)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods callbacks :: Lens' Operation (InsOrdHashMap Text (Referenced Callback)) # | |||||||||||||
HasEncoding MediaTypeObject (InsOrdHashMap Text Encoding) | |||||||||||||
Defined in Data.OpenApi.Lens Methods encoding :: Lens' MediaTypeObject (InsOrdHashMap Text Encoding) # | |||||||||||||
HasExamples Header (InsOrdHashMap Text (Referenced Example)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods examples :: Lens' Header (InsOrdHashMap Text (Referenced Example)) # | |||||||||||||
HasExamples MediaTypeObject (InsOrdHashMap Text (Referenced Example)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods examples :: Lens' MediaTypeObject (InsOrdHashMap Text (Referenced Example)) # | |||||||||||||
HasExamples Param (InsOrdHashMap Text (Referenced Example)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods examples :: Lens' Param (InsOrdHashMap Text (Referenced Example)) # | |||||||||||||
HasHeaders Encoding (InsOrdHashMap Text (Referenced Header)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods headers :: Lens' Encoding (InsOrdHashMap Text (Referenced Header)) # | |||||||||||||
HasHeaders Response (InsOrdHashMap HeaderName (Referenced Header)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods headers :: Lens' Response (InsOrdHashMap HeaderName (Referenced Header)) # | |||||||||||||
HasLinks Response (InsOrdHashMap Text (Referenced Link)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods links :: Lens' Response (InsOrdHashMap Text (Referenced Link)) # | |||||||||||||
HasMapping Discriminator (InsOrdHashMap Text Text) | |||||||||||||
Defined in Data.OpenApi.Lens Methods | |||||||||||||
HasParameters Link (InsOrdHashMap Text ExpressionOrValue) | |||||||||||||
Defined in Data.OpenApi.Lens Methods parameters :: Lens' Link (InsOrdHashMap Text ExpressionOrValue) # | |||||||||||||
HasProperties Schema (InsOrdHashMap Text (Referenced Schema)) | |||||||||||||
Defined in Data.OpenApi.Lens Methods properties :: Lens' Schema (InsOrdHashMap Text (Referenced Schema)) # | |||||||||||||
HasVariables Server (InsOrdHashMap Text ServerVariable) | |||||||||||||
Defined in Data.OpenApi.Lens Methods variables :: Lens' Server (InsOrdHashMap Text ServerVariable) # | |||||||||||||
HasExtensions Operation (InsOrdHashMap Text Value) | |||||||||||||
Defined in Data.Swagger.Lens Methods | |||||||||||||
HasHeaders Response (InsOrdHashMap HeaderName Header) | |||||||||||||
Defined in Data.Swagger.Lens Methods headers :: Lens' Response (InsOrdHashMap HeaderName Header) # | |||||||||||||
HasProperties Schema (InsOrdHashMap Text (Referenced Schema)) | |||||||||||||
Defined in Data.Swagger.Lens Methods properties :: Lens' Schema (InsOrdHashMap Text (Referenced Schema)) # | |||||||||||||
Stream (NoShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream Associated Types
Methods tokenToChunk :: Proxy (NoShareInput Text) -> Token (NoShareInput Text) -> Tokens (NoShareInput Text) # tokensToChunk :: Proxy (NoShareInput Text) -> [Token (NoShareInput Text)] -> Tokens (NoShareInput Text) # chunkToTokens :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> [Token (NoShareInput Text)] # chunkLength :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> Int # chunkEmpty :: Proxy (NoShareInput Text) -> Tokens (NoShareInput Text) -> Bool # take1_ :: NoShareInput Text -> Maybe (Token (NoShareInput Text), NoShareInput Text) # takeN_ :: Int -> NoShareInput Text -> Maybe (Tokens (NoShareInput Text), NoShareInput Text) # takeWhile_ :: (Token (NoShareInput Text) -> Bool) -> NoShareInput Text -> (Tokens (NoShareInput Text), NoShareInput Text) # | |||||||||||||
Stream (ShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream Associated Types
Methods tokenToChunk :: Proxy (ShareInput Text) -> Token (ShareInput Text) -> Tokens (ShareInput Text) # tokensToChunk :: Proxy (ShareInput Text) -> [Token (ShareInput Text)] -> Tokens (ShareInput Text) # chunkToTokens :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> [Token (ShareInput Text)] # chunkLength :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> Int # chunkEmpty :: Proxy (ShareInput Text) -> Tokens (ShareInput Text) -> Bool # take1_ :: ShareInput Text -> Maybe (Token (ShareInput Text), ShareInput Text) # takeN_ :: Int -> ShareInput Text -> Maybe (Tokens (ShareInput Text), ShareInput Text) # takeWhile_ :: (Token (ShareInput Text) -> Bool) -> ShareInput Text -> (Tokens (ShareInput Text), ShareInput Text) # | |||||||||||||
FromField (CI Text) | citext | ||||||||||||
Defined in Database.PostgreSQL.Simple.FromField Methods fromField :: FieldParser (CI Text) # | |||||||||||||
ToField (CI Text) | citext | ||||||||||||
HasFormat (ParamSchema t) (Maybe Format) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
HasPattern (ParamSchema t) (Maybe Pattern) | |||||||||||||
Defined in Data.Swagger.Lens | |||||||||||||
FromJSON (Text, Metric) | |||||||||||||
ToJSON (Text, Metric) | |||||||||||||
FromHttpApiData a => FromDeepQuery (Map Text a) | |||||||||||||
Defined in Servant.API.QueryString | |||||||||||||
ToSample (Text, Metric) | |||||||||||||
type ChunkElem Text | |||||||||||||
Defined in Data.Attoparsec.Internal.Types | |||||||||||||
type State Text | |||||||||||||
Defined in Data.Attoparsec.Internal.Types | |||||||||||||
type Item Text | |||||||||||||
type Index Text | |||||||||||||
Defined in Control.Lens.At | |||||||||||||
type IxValue Text | |||||||||||||
Defined in Control.Lens.At | |||||||||||||
type Token Text | |||||||||||||
Defined in Text.Megaparsec.Stream | |||||||||||||
type Tokens Text | |||||||||||||
Defined in Text.Megaparsec.Stream | |||||||||||||
type Element Text | |||||||||||||
Defined in Data.MonoTraversable | |||||||||||||
type Index Text | |||||||||||||
Defined in Data.Sequences | |||||||||||||
type Index Text | |||||||||||||
type IxKind Text | |||||||||||||
Defined in Optics.At | |||||||||||||
type IxValue Text | |||||||||||||
type ToBuiltin Text | |||||||||||||
Defined in PlutusTx.Builtins.HasBuiltin | |||||||||||||
type IsBuiltin DefaultUni Text | |||||||||||||
Defined in PlutusCore.Default.Universe | |||||||||||||
type ToBinds DefaultUni acc Text | |||||||||||||
Defined in PlutusCore.Default.Universe | |||||||||||||
type ToHoles DefaultUni hole Text | |||||||||||||
Defined in PlutusCore.Default.Universe | |||||||||||||
type Token (NoShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream | |||||||||||||
type Token (ShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream | |||||||||||||
type Tokens (NoShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream | |||||||||||||
type Tokens (ShareInput Text) | |||||||||||||
Defined in Text.Megaparsec.Stream |
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
>>>
:{
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack) :}
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
@since base-4.8.1.0
Instances
NFData CallStack | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
IsList CallStack | Be aware that 'fromList . toList = id' only for unfrozen @since base-4.9.0.0 |
Show CallStack | @since base-4.9.0.0 |
NoThunks CallStack | Since CallStacks can't retain application data, we don't want to check them for thunks at all |
type Code CallStack | |
type DatatypeInfoOf CallStack | |
Defined in Generics.SOP.Instances type DatatypeInfoOf CallStack = 'ADT "GHC.Internal.Stack.Types" "CallStack" '['Constructor "EmptyCallStack", 'Constructor "PushCallStack", 'Constructor "FreezeCallStack"] '['[] :: [StrictnessInfo], '['StrictnessInfo 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy, 'StrictnessInfo 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy, 'StrictnessInfo 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy], '['StrictnessInfo 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy]] | |
type Item CallStack | |
Defined in GHC.Internal.IsList |
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
class Contravariant (f :: Type -> Type) where #
The class of contravariant functors.
Whereas in Haskell, one can think of a Functor
as containing or producing
values, a contravariant functor is a functor that can be thought of as
consuming values.
As an example, consider the type of predicate functions a -> Bool
. One
such predicate might be negative x = x < 0
, which
classifies integers as to whether they are negative. However, given this
predicate, we can re-use it in other situations, providing we have a way to
map values to integers. For instance, we can use the negative
predicate
on a person's bank balance to work out if they are currently overdrawn:
newtype Predicate a = Predicate { getPredicate :: a -> Bool } instance Contravariant Predicate where contramap :: (a' -> a) -> (Predicate a -> Predicate a') contramap f (Predicate p) = Predicate (p . f) | `- First, map the input... `----- then apply the predicate. overdrawn :: Predicate Person overdrawn = contramap personBankBalance negative
Any instance should be subject to the following laws:
Note, that the second law follows from the free theorem of the type of
contramap
and the first law, so you need only check that the former
condition holds.
Minimal complete definition
Instances
Contravariant ToJSONKeyFunction | |
Defined in Data.Aeson.Types.ToJSON Methods contramap :: (a' -> a) -> ToJSONKeyFunction a -> ToJSONKeyFunction a' # (>$) :: b -> ToJSONKeyFunction b -> ToJSONKeyFunction a # | |
Contravariant Comparison | A |
Defined in Data.Functor.Contravariant Methods contramap :: (a' -> a) -> Comparison a -> Comparison a' # (>$) :: b -> Comparison b -> Comparison a # | |
Contravariant Equivalence | Equivalence relations are |
Defined in Data.Functor.Contravariant Methods contramap :: (a' -> a) -> Equivalence a -> Equivalence a' # (>$) :: b -> Equivalence b -> Equivalence a # | |
Contravariant Predicate | A Without newtypes contramap :: (a' -> a) -> (Predicate a -> Predicate a') contramap f (Predicate g) = Predicate (g . f) |
Contravariant (Op a) | |
Contravariant (Tracer m) | |
Contravariant (Proxy :: Type -> Type) | |
Contravariant (U1 :: Type -> Type) | |
Contravariant (V1 :: Type -> Type) | |
Contravariant f => Contravariant (Indexing f) | |
Contravariant f => Contravariant (Indexing64 f) | |
Defined in Control.Lens.Internal.Indexed Methods contramap :: (a' -> a) -> Indexing64 f a -> Indexing64 f a' # (>$) :: b -> Indexing64 f b -> Indexing64 f a # | |
Contravariant m => Contravariant (FirstToFinish m) | |
Defined in Data.Monoid.Synchronisation Methods contramap :: (a' -> a) -> FirstToFinish m a -> FirstToFinish m a' # (>$) :: b -> FirstToFinish m b -> FirstToFinish m a # | |
Monad m => Contravariant (Trace m) | Contramap lifted to Trace |
Contravariant m => Contravariant (MaybeT m) | |
Contravariant (Const a :: Type -> Type) | |
Contravariant f => Contravariant (Alt f) | |
Contravariant f => Contravariant (Rec1 f) | |
Contravariant f => Contravariant (AlongsideLeft f b) | |
Defined in Control.Lens.Internal.Getter Methods contramap :: (a' -> a) -> AlongsideLeft f b a -> AlongsideLeft f b a' # (>$) :: b0 -> AlongsideLeft f b b0 -> AlongsideLeft f b a # | |
Contravariant f => Contravariant (AlongsideRight f a) | |
Defined in Control.Lens.Internal.Getter Methods contramap :: (a' -> a0) -> AlongsideRight f a a0 -> AlongsideRight f a a' # (>$) :: b -> AlongsideRight f a b -> AlongsideRight f a a0 # | |
Contravariant (Effect m r) | |
Contravariant f => Contravariant (Backwards f) | Derived instance. |
Contravariant m => Contravariant (ExceptT e m) | |
Contravariant f => Contravariant (IdentityT f) | |
Contravariant m => Contravariant (ReaderT r m) | |
Contravariant m => Contravariant (StateT s m) | |
Contravariant m => Contravariant (StateT s m) | |
Contravariant m => Contravariant (WriterT w m) | |
Contravariant m => Contravariant (WriterT w m) | |
Contravariant (Constant a :: Type -> Type) | |
Contravariant f => Contravariant (Reverse f) | Derived instance. |
(Contravariant f, Contravariant g) => Contravariant (Product f g) | |
(Contravariant f, Contravariant g) => Contravariant (Sum f g) | |
(Contravariant f, Contravariant g) => Contravariant (f :*: g) | |
(Contravariant f, Contravariant g) => Contravariant (f :+: g) | |
Contravariant (K1 i c :: Type -> Type) | |
(Functor f, Contravariant g) => Contravariant (Compose f g) | |
(Functor f, Contravariant g) => Contravariant (f :.: g) | |
Contravariant f => Contravariant (M1 i c f) | |
(Profunctor p, Contravariant g) => Contravariant (BazaarT p g a b) | |
(Profunctor p, Contravariant g) => Contravariant (BazaarT1 p g a b) | |
(Profunctor p, Contravariant g) => Contravariant (PretextT p g a b) | |
Contravariant f => Contravariant (TakingWhile p f a b) | |
Defined in Control.Lens.Internal.Magma Methods contramap :: (a' -> a0) -> TakingWhile p f a b a0 -> TakingWhile p f a b a' # (>$) :: b0 -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 # | |
Contravariant (EffectRWS w st m s) | |
Contravariant m => Contravariant (RWST r w s m) | |
Contravariant m => Contravariant (RWST r w s m) | |
A type that can be converted to JSON.
Instances in general must specify toJSON
and should (but don't need
to) specify toEncoding
.
An example type and instance:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceToJSON
Coord wheretoJSON
(Coord x y) =object
["x".=
x, "y".=
y]toEncoding
(Coord x y) =pairs
("x".=
x<>
"y".=
y)
Instead of manually writing your ToJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
toJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance. If you require nothing other than
defaultOptions
, it is sufficient to write (and this is the only
alternative where the default toJSON
implementation is sufficient):
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
or more conveniently using the DerivingVia extension
deriving viaGenerically
Coord instanceToJSON
Coord
If on the other hand you wish to customize the generic decoding, you have to implement both methods:
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceToJSON
Coord wheretoJSON
=genericToJSON
customOptionstoEncoding
=genericToEncoding
customOptions
Previous versions of this library only had the toJSON
method. Adding
toEncoding
had two reasons:
toEncoding
is more efficient for the common case that the output oftoJSON
is directly serialized to aByteString
. Further, expressing either method in terms of the other would be non-optimal.- The choice of defaults allows a smooth transition for existing users:
Existing instances that do not define
toEncoding
still compile and have the correct semantics. This is ensured by making the default implementation oftoEncoding
usetoJSON
. This produces correct results, but since it performs an intermediate conversion to aValue
, it will be less efficient than directly emitting anEncoding
. (this also means that specifying nothing more thaninstance ToJSON Coord
would be sufficient as a generically decoding instance, but there probably exists no good reason to not specifytoEncoding
in new instances.)
Minimal complete definition
Nothing
Methods
Convert a Haskell value to a JSON-friendly intermediate type.
toEncoding :: a -> Encoding #
Encode a Haskell value as JSON.
The default implementation of this method creates an
intermediate Value
using toJSON
. This provides
source-level compatibility for people upgrading from older
versions of this library, but obviously offers no performance
advantage.
To benefit from direct encoding, you must provide an
implementation for this method. The easiest way to do so is by
having your types implement Generic
using the DeriveGeneric
extension, and then have GHC generate a method body as follows.
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
toJSONList :: [a] -> Value #
toEncodingList :: [a] -> Encoding #
Defines when it is acceptable to omit a field of this type from a record.
Used by (
operator, and Generics and TH deriving
with .?=
)
.omitNothingFields
= True
Since: aeson-2.2.0.0
Instances
ToJSON Key | |
ToJSON DotNetTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: DotNetTime -> Value # toEncoding :: DotNetTime -> Encoding # toJSONList :: [DotNetTime] -> Value # toEncodingList :: [DotNetTime] -> Encoding # omitField :: DotNetTime -> Bool # | |
ToJSON Value | |
ToJSON GYAddress # |
|
ToJSON GYAddressBech32 # |
|
Defined in GeniusYield.Types.Address Methods toJSON :: GYAddressBech32 -> Value # toEncoding :: GYAddressBech32 -> Encoding # toJSONList :: [GYAddressBech32] -> Value # toEncodingList :: [GYAddressBech32] -> Encoding # omitField :: GYAddressBech32 -> Bool # | |
ToJSON GYStakeAddress # |
|
Defined in GeniusYield.Types.Address Methods toJSON :: GYStakeAddress -> Value # toEncoding :: GYStakeAddress -> Encoding # toJSONList :: [GYStakeAddress] -> Value # toEncodingList :: [GYStakeAddress] -> Encoding # omitField :: GYStakeAddress -> Bool # | |
ToJSON GYStakeAddressBech32 # |
|
Defined in GeniusYield.Types.Address Methods toJSON :: GYStakeAddressBech32 -> Value # toEncoding :: GYStakeAddressBech32 -> Encoding # toJSONList :: [GYStakeAddressBech32] -> Value # toEncodingList :: [GYStakeAddressBech32] -> Encoding # omitField :: GYStakeAddressBech32 -> Bool # | |
ToJSON GYAnchorDataHash # | |
Defined in GeniusYield.Types.Anchor Methods toJSON :: GYAnchorDataHash -> Value # toEncoding :: GYAnchorDataHash -> Encoding # toJSONList :: [GYAnchorDataHash] -> Value # toEncodingList :: [GYAnchorDataHash] -> Encoding # omitField :: GYAnchorDataHash -> Bool # | |
ToJSON GYUrl # | |
ToJSON ArgumentBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Argument Methods toJSON :: ArgumentBlueprint -> Value # toEncoding :: ArgumentBlueprint -> Encoding # toJSONList :: [ArgumentBlueprint] -> Value # toEncodingList :: [ArgumentBlueprint] -> Encoding # omitField :: ArgumentBlueprint -> Bool # | |
ToJSON ContractBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Contract Methods toJSON :: ContractBlueprint -> Value # toEncoding :: ContractBlueprint -> Encoding # toJSONList :: [ContractBlueprint] -> Value # toEncodingList :: [ContractBlueprint] -> Encoding # omitField :: ContractBlueprint -> Bool # | |
ToJSON DefinitionId # | |
Defined in GeniusYield.Types.Blueprint.DefinitionId Methods toJSON :: DefinitionId -> Value # toEncoding :: DefinitionId -> Encoding # toJSONList :: [DefinitionId] -> Value # toEncodingList :: [DefinitionId] -> Encoding # omitField :: DefinitionId -> Bool # | |
ToJSON ParameterBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Parameter Methods toJSON :: ParameterBlueprint -> Value # toEncoding :: ParameterBlueprint -> Encoding # toJSONList :: [ParameterBlueprint] -> Value # toEncodingList :: [ParameterBlueprint] -> Encoding # omitField :: ParameterBlueprint -> Bool # | |
ToJSON Preamble # | |
ToJSON Purpose # | |
ToJSON Schema # | |
ToJSON ValidatorBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Validator Methods toJSON :: ValidatorBlueprint -> Value # toEncoding :: ValidatorBlueprint -> Encoding # toJSONList :: [ValidatorBlueprint] -> Value # toEncodingList :: [ValidatorBlueprint] -> Encoding # omitField :: ValidatorBlueprint -> Bool # | |
ToJSON GYDatum # |
|
ToJSON GYDatumHash # | |
Defined in GeniusYield.Types.Datum Methods toJSON :: GYDatumHash -> Value # toEncoding :: GYDatumHash -> Encoding # toJSONList :: [GYDatumHash] -> Value # toEncodingList :: [GYDatumHash] -> Encoding # omitField :: GYDatumHash -> Bool # | |
ToJSON GYLogScribeConfig # |
|
Defined in GeniusYield.Types.Logging Methods toJSON :: GYLogScribeConfig -> Value # toEncoding :: GYLogScribeConfig -> Encoding # toJSONList :: [GYLogScribeConfig] -> Value # toEncodingList :: [GYLogScribeConfig] -> Encoding # omitField :: GYLogScribeConfig -> Bool # | |
ToJSON GYLogScribeType # |
|
Defined in GeniusYield.Types.Logging Methods toJSON :: GYLogScribeType -> Value # toEncoding :: GYLogScribeType -> Encoding # toJSONList :: [GYLogScribeType] -> Value # toEncodingList :: [GYLogScribeType] -> Encoding # omitField :: GYLogScribeType -> Bool # | |
ToJSON GYLogSeverity # | |
Defined in GeniusYield.Types.Logging Methods toJSON :: GYLogSeverity -> Value # toEncoding :: GYLogSeverity -> Encoding # toJSONList :: [GYLogSeverity] -> Value # toEncodingList :: [GYLogSeverity] -> Encoding # omitField :: GYLogSeverity -> Bool # | |
ToJSON GYLogVerbosity # | |
Defined in GeniusYield.Types.Logging Methods toJSON :: GYLogVerbosity -> Value # toEncoding :: GYLogVerbosity -> Encoding # toJSONList :: [GYLogVerbosity] -> Value # toEncodingList :: [GYLogVerbosity] -> Encoding # omitField :: GYLogVerbosity -> Bool # | |
ToJSON LogSrc # | |
ToJSON GYNatural # |
|
ToJSON GYNetworkId # |
|
Defined in GeniusYield.Types.NetworkId Methods toJSON :: GYNetworkId -> Value # toEncoding :: GYNetworkId -> Encoding # toJSONList :: [GYNetworkId] -> Value # toEncodingList :: [GYNetworkId] -> Encoding # omitField :: GYNetworkId -> Bool # | |
ToJSON GYNetworkInfo # | |
Defined in GeniusYield.Types.NetworkId Methods toJSON :: GYNetworkInfo -> Value # toEncoding :: GYNetworkInfo -> Encoding # toJSONList :: [GYNetworkInfo] -> Value # toEncodingList :: [GYNetworkInfo] -> Encoding # omitField :: GYNetworkInfo -> Bool # | |
ToJSON GYPubKeyHash # |
|
Defined in GeniusYield.Types.PubKeyHash Methods toJSON :: GYPubKeyHash -> Value # toEncoding :: GYPubKeyHash -> Encoding # toJSONList :: [GYPubKeyHash] -> Value # toEncodingList :: [GYPubKeyHash] -> Encoding # omitField :: GYPubKeyHash -> Bool # | |
ToJSON GYRational # |
|
Defined in GeniusYield.Types.Rational Methods toJSON :: GYRational -> Value # toEncoding :: GYRational -> Encoding # toJSONList :: [GYRational] -> Value # toEncodingList :: [GYRational] -> Encoding # omitField :: GYRational -> Bool # | |
ToJSON GYMintingPolicyId # | |
Defined in GeniusYield.Types.Script Methods toJSON :: GYMintingPolicyId -> Value # toEncoding :: GYMintingPolicyId -> Encoding # toJSONList :: [GYMintingPolicyId] -> Value # toEncodingList :: [GYMintingPolicyId] -> Encoding # omitField :: GYMintingPolicyId -> Bool # | |
ToJSON GYScriptHash # | |
Defined in GeniusYield.Types.Script.ScriptHash Methods toJSON :: GYScriptHash -> Value # toEncoding :: GYScriptHash -> Encoding # toJSONList :: [GYScriptHash] -> Value # toEncodingList :: [GYScriptHash] -> Encoding # omitField :: GYScriptHash -> Bool # | |
ToJSON GYSimpleScript # | |
Defined in GeniusYield.Types.Script.SimpleScript Methods toJSON :: GYSimpleScript -> Value # toEncoding :: GYSimpleScript -> Encoding # toJSONList :: [GYSimpleScript] -> Value # toEncodingList :: [GYSimpleScript] -> Encoding # omitField :: GYSimpleScript -> Bool # | |
ToJSON GYSlot # | |
ToJSON GYStakePoolIdBech32 # |
|
Defined in GeniusYield.Types.StakePoolId Methods toJSON :: GYStakePoolIdBech32 -> Value # toEncoding :: GYStakePoolIdBech32 -> Encoding # toJSONList :: [GYStakePoolIdBech32] -> Value # toEncodingList :: [GYStakePoolIdBech32] -> Encoding # omitField :: GYStakePoolIdBech32 -> Bool # | |
ToJSON GYTime # |
|
ToJSON GYTx # |
|
ToJSON GYTxId # |
|
ToJSON GYTxOutRef # | |
Defined in GeniusYield.Types.TxOutRef Methods toJSON :: GYTxOutRef -> Value # toEncoding :: GYTxOutRef -> Encoding # toJSONList :: [GYTxOutRef] -> Value # toEncodingList :: [GYTxOutRef] -> Encoding # omitField :: GYTxOutRef -> Bool # | |
ToJSON GYTxOutRefCbor # | Warning: this JSON instance does not satisfy
In practise, this shouldn't be an issue -- see https://github.com/geniusyield/atlas/issues/399#issuecomment-2618617724 for details. |
Defined in GeniusYield.Types.TxOutRef Methods toJSON :: GYTxOutRefCbor -> Value # toEncoding :: GYTxOutRefCbor -> Encoding # toJSONList :: [GYTxOutRefCbor] -> Value # toEncodingList :: [GYTxOutRefCbor] -> Encoding # omitField :: GYTxOutRefCbor -> Bool # | |
ToJSON GYAssetClass # |
|
Defined in GeniusYield.Types.Value Methods toJSON :: GYAssetClass -> Value # toEncoding :: GYAssetClass -> Encoding # toJSONList :: [GYAssetClass] -> Value # toEncodingList :: [GYAssetClass] -> Encoding # omitField :: GYAssetClass -> Bool # | |
ToJSON GYTokenName # |
|
Defined in GeniusYield.Types.Value Methods toJSON :: GYTokenName -> Value # toEncoding :: GYTokenName -> Encoding # toJSONList :: [GYTokenName] -> Value # toEncodingList :: [GYTokenName] -> Encoding # omitField :: GYTokenName -> Bool # | |
ToJSON GYValue # |
|
ToJSON ByteString64 | |
Defined in Data.ByteString.Base64.Type Methods toJSON :: ByteString64 -> Value # toEncoding :: ByteString64 -> Encoding # toJSONList :: [ByteString64] -> Value # toEncodingList :: [ByteString64] -> Encoding # omitField :: ByteString64 -> Bool # | |
ToJSON ApiError | |
ToJSON AccountDelegation | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountDelegation -> Value # toEncoding :: AccountDelegation -> Encoding # toJSONList :: [AccountDelegation] -> Value # toEncodingList :: [AccountDelegation] -> Encoding # omitField :: AccountDelegation -> Bool # | |
ToJSON AccountHistory | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountHistory -> Value # toEncoding :: AccountHistory -> Encoding # toJSONList :: [AccountHistory] -> Value # toEncodingList :: [AccountHistory] -> Encoding # omitField :: AccountHistory -> Bool # | |
ToJSON AccountInfo | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountInfo -> Value # toEncoding :: AccountInfo -> Encoding # toJSONList :: [AccountInfo] -> Value # toEncodingList :: [AccountInfo] -> Encoding # omitField :: AccountInfo -> Bool # | |
ToJSON AccountMir | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountMir -> Value # toEncoding :: AccountMir -> Encoding # toJSONList :: [AccountMir] -> Value # toEncodingList :: [AccountMir] -> Encoding # omitField :: AccountMir -> Bool # | |
ToJSON AccountRegistration | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountRegistration -> Value # toEncoding :: AccountRegistration -> Encoding # toJSONList :: [AccountRegistration] -> Value # toEncodingList :: [AccountRegistration] -> Encoding # omitField :: AccountRegistration -> Bool # | |
ToJSON AccountRegistrationAction | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountRegistrationAction -> Value # toEncoding :: AccountRegistrationAction -> Encoding # toJSONList :: [AccountRegistrationAction] -> Value # | |
ToJSON AccountReward | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountReward -> Value # toEncoding :: AccountReward -> Encoding # toJSONList :: [AccountReward] -> Value # toEncodingList :: [AccountReward] -> Encoding # omitField :: AccountReward -> Bool # | |
ToJSON AccountWithdrawal | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AccountWithdrawal -> Value # toEncoding :: AccountWithdrawal -> Encoding # toJSONList :: [AccountWithdrawal] -> Value # toEncodingList :: [AccountWithdrawal] -> Encoding # omitField :: AccountWithdrawal -> Bool # | |
ToJSON AddressAssociated | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AddressAssociated -> Value # toEncoding :: AddressAssociated -> Encoding # toJSONList :: [AddressAssociated] -> Value # toEncodingList :: [AddressAssociated] -> Encoding # omitField :: AddressAssociated -> Bool # | |
ToJSON AddressAssociatedTotal | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: AddressAssociatedTotal -> Value # toEncoding :: AddressAssociatedTotal -> Encoding # toJSONList :: [AddressAssociatedTotal] -> Value # toEncodingList :: [AddressAssociatedTotal] -> Encoding # omitField :: AddressAssociatedTotal -> Bool # | |
ToJSON RewardType | |
Defined in Blockfrost.Types.Cardano.Accounts Methods toJSON :: RewardType -> Value # toEncoding :: RewardType -> Encoding # toJSONList :: [RewardType] -> Value # toEncodingList :: [RewardType] -> Encoding # omitField :: RewardType -> Bool # | |
ToJSON AddressDetails | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressDetails -> Value # toEncoding :: AddressDetails -> Encoding # toJSONList :: [AddressDetails] -> Value # toEncodingList :: [AddressDetails] -> Encoding # omitField :: AddressDetails -> Bool # | |
ToJSON AddressInfo | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |
ToJSON AddressInfoExtended | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressInfoExtended -> Value # toEncoding :: AddressInfoExtended -> Encoding # toJSONList :: [AddressInfoExtended] -> Value # toEncodingList :: [AddressInfoExtended] -> Encoding # omitField :: AddressInfoExtended -> Bool # | |
ToJSON AddressTransaction | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressTransaction -> Value # toEncoding :: AddressTransaction -> Encoding # toJSONList :: [AddressTransaction] -> Value # toEncodingList :: [AddressTransaction] -> Encoding # omitField :: AddressTransaction -> Bool # | |
ToJSON AddressType | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressType -> Value # toEncoding :: AddressType -> Encoding # toJSONList :: [AddressType] -> Value # toEncodingList :: [AddressType] -> Encoding # omitField :: AddressType -> Bool # | |
ToJSON AddressUtxo | |
Defined in Blockfrost.Types.Cardano.Addresses Methods toJSON :: AddressUtxo -> Value # toEncoding :: AddressUtxo -> Encoding # toJSONList :: [AddressUtxo] -> Value # toEncodingList :: [AddressUtxo] -> Encoding # omitField :: AddressUtxo -> Bool # | |
ToJSON AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetAction -> Value # toEncoding :: AssetAction -> Encoding # toJSONList :: [AssetAction] -> Value # toEncodingList :: [AssetAction] -> Encoding # omitField :: AssetAction -> Bool # | |
ToJSON AssetAddress | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetAddress -> Value # toEncoding :: AssetAddress -> Encoding # toJSONList :: [AssetAddress] -> Value # toEncodingList :: [AssetAddress] -> Encoding # omitField :: AssetAddress -> Bool # | |
ToJSON AssetDetails | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetDetails -> Value # toEncoding :: AssetDetails -> Encoding # toJSONList :: [AssetDetails] -> Value # toEncodingList :: [AssetDetails] -> Encoding # omitField :: AssetDetails -> Bool # | |
ToJSON AssetHistory | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetHistory -> Value # toEncoding :: AssetHistory -> Encoding # toJSONList :: [AssetHistory] -> Value # toEncodingList :: [AssetHistory] -> Encoding # omitField :: AssetHistory -> Bool # | |
ToJSON AssetInfo | |
ToJSON AssetMetadata | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetMetadata -> Value # toEncoding :: AssetMetadata -> Encoding # toJSONList :: [AssetMetadata] -> Value # toEncodingList :: [AssetMetadata] -> Encoding # omitField :: AssetMetadata -> Bool # | |
ToJSON AssetOnChainMetadata | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetOnChainMetadata -> Value # toEncoding :: AssetOnChainMetadata -> Encoding # toJSONList :: [AssetOnChainMetadata] -> Value # toEncodingList :: [AssetOnChainMetadata] -> Encoding # omitField :: AssetOnChainMetadata -> Bool # | |
ToJSON AssetTransaction | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: AssetTransaction -> Value # toEncoding :: AssetTransaction -> Encoding # toJSONList :: [AssetTransaction] -> Value # toEncodingList :: [AssetTransaction] -> Encoding # omitField :: AssetTransaction -> Bool # | |
ToJSON MetadataMediaFile | |
Defined in Blockfrost.Types.Cardano.Assets Methods toJSON :: MetadataMediaFile -> Value # toEncoding :: MetadataMediaFile -> Encoding # toJSONList :: [MetadataMediaFile] -> Value # toEncodingList :: [MetadataMediaFile] -> Encoding # omitField :: MetadataMediaFile -> Bool # | |
ToJSON Block | |
ToJSON TxHashCBOR | |
Defined in Blockfrost.Types.Cardano.Blocks Methods toJSON :: TxHashCBOR -> Value # toEncoding :: TxHashCBOR -> Encoding # toJSONList :: [TxHashCBOR] -> Value # toEncodingList :: [TxHashCBOR] -> Encoding # omitField :: TxHashCBOR -> Bool # | |
ToJSON CostModels | |
Defined in Blockfrost.Types.Cardano.Epochs Methods toJSON :: CostModels -> Value # toEncoding :: CostModels -> Encoding # toJSONList :: [CostModels] -> Value # toEncodingList :: [CostModels] -> Encoding # omitField :: CostModels -> Bool # | |
ToJSON CostModelsRaw | |
Defined in Blockfrost.Types.Cardano.Epochs Methods toJSON :: CostModelsRaw -> Value # toEncoding :: CostModelsRaw -> Encoding # toJSONList :: [CostModelsRaw] -> Value # toEncodingList :: [CostModelsRaw] -> Encoding # omitField :: CostModelsRaw -> Bool # | |
ToJSON EpochInfo | |
ToJSON PoolStakeDistribution | |
Defined in Blockfrost.Types.Cardano.Epochs Methods toJSON :: PoolStakeDistribution -> Value # toEncoding :: PoolStakeDistribution -> Encoding # toJSONList :: [PoolStakeDistribution] -> Value # toEncodingList :: [PoolStakeDistribution] -> Encoding # omitField :: PoolStakeDistribution -> Bool # | |
ToJSON ProtocolParams | |
Defined in Blockfrost.Types.Cardano.Epochs Methods toJSON :: ProtocolParams -> Value # toEncoding :: ProtocolParams -> Encoding # toJSONList :: [ProtocolParams] -> Value # toEncodingList :: [ProtocolParams] -> Encoding # omitField :: ProtocolParams -> Bool # | |
ToJSON StakeDistribution | |
Defined in Blockfrost.Types.Cardano.Epochs Methods toJSON :: StakeDistribution -> Value # toEncoding :: StakeDistribution -> Encoding # toJSONList :: [StakeDistribution] -> Value # toEncodingList :: [StakeDistribution] -> Encoding # omitField :: StakeDistribution -> Bool # | |
ToJSON Genesis | |
ToJSON MempoolRedeemer | |
Defined in Blockfrost.Types.Cardano.Mempool Methods toJSON :: MempoolRedeemer -> Value # toEncoding :: MempoolRedeemer -> Encoding # toJSONList :: [MempoolRedeemer] -> Value # toEncodingList :: [MempoolRedeemer] -> Encoding # omitField :: MempoolRedeemer -> Bool # | |
ToJSON MempoolTransaction | |
Defined in Blockfrost.Types.Cardano.Mempool Methods toJSON :: MempoolTransaction -> Value # toEncoding :: MempoolTransaction -> Encoding # toJSONList :: [MempoolTransaction] -> Value # toEncodingList :: [MempoolTransaction] -> Encoding # omitField :: MempoolTransaction -> Bool # | |
ToJSON MempoolUTxOInput | |
Defined in Blockfrost.Types.Cardano.Mempool Methods toJSON :: MempoolUTxOInput -> Value # toEncoding :: MempoolUTxOInput -> Encoding # toJSONList :: [MempoolUTxOInput] -> Value # toEncodingList :: [MempoolUTxOInput] -> Encoding # omitField :: MempoolUTxOInput -> Bool # | |
ToJSON TransactionInMempool | |
Defined in Blockfrost.Types.Cardano.Mempool Methods toJSON :: TransactionInMempool -> Value # toEncoding :: TransactionInMempool -> Encoding # toJSONList :: [TransactionInMempool] -> Value # toEncodingList :: [TransactionInMempool] -> Encoding # omitField :: TransactionInMempool -> Bool # | |
ToJSON TxMeta | |
ToJSON TxMetaCBOR | |
Defined in Blockfrost.Types.Cardano.Metadata Methods toJSON :: TxMetaCBOR -> Value # toEncoding :: TxMetaCBOR -> Encoding # toJSONList :: [TxMetaCBOR] -> Value # toEncodingList :: [TxMetaCBOR] -> Encoding # omitField :: TxMetaCBOR -> Bool # | |
ToJSON TxMetaJSON | |
Defined in Blockfrost.Types.Cardano.Metadata Methods toJSON :: TxMetaJSON -> Value # toEncoding :: TxMetaJSON -> Encoding # toJSONList :: [TxMetaJSON] -> Value # toEncodingList :: [TxMetaJSON] -> Encoding # omitField :: TxMetaJSON -> Bool # | |
ToJSON Network | |
ToJSON NetworkEraBound | |
Defined in Blockfrost.Types.Cardano.Network Methods toJSON :: NetworkEraBound -> Value # toEncoding :: NetworkEraBound -> Encoding # toJSONList :: [NetworkEraBound] -> Value # toEncodingList :: [NetworkEraBound] -> Encoding # omitField :: NetworkEraBound -> Bool # | |
ToJSON NetworkEraParameters | |
Defined in Blockfrost.Types.Cardano.Network Methods toJSON :: NetworkEraParameters -> Value # toEncoding :: NetworkEraParameters -> Encoding # toJSONList :: [NetworkEraParameters] -> Value # toEncodingList :: [NetworkEraParameters] -> Encoding # omitField :: NetworkEraParameters -> Bool # | |
ToJSON NetworkEraSummary | |
Defined in Blockfrost.Types.Cardano.Network Methods toJSON :: NetworkEraSummary -> Value # toEncoding :: NetworkEraSummary -> Encoding # toJSONList :: [NetworkEraSummary] -> Value # toEncodingList :: [NetworkEraSummary] -> Encoding # omitField :: NetworkEraSummary -> Bool # | |
ToJSON NetworkStake | |
Defined in Blockfrost.Types.Cardano.Network Methods toJSON :: NetworkStake -> Value # toEncoding :: NetworkStake -> Encoding # toJSONList :: [NetworkStake] -> Value # toEncodingList :: [NetworkStake] -> Encoding # omitField :: NetworkStake -> Bool # | |
ToJSON NetworkSupply | |
Defined in Blockfrost.Types.Cardano.Network Methods toJSON :: NetworkSupply -> Value # toEncoding :: NetworkSupply -> Encoding # toJSONList :: [NetworkSupply] -> Value # toEncodingList :: [NetworkSupply] -> Encoding # omitField :: NetworkSupply -> Bool # | |
ToJSON Pool | |
ToJSON PoolDelegator | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolDelegator -> Value # toEncoding :: PoolDelegator -> Encoding # toJSONList :: [PoolDelegator] -> Value # toEncodingList :: [PoolDelegator] -> Encoding # omitField :: PoolDelegator -> Bool # | |
ToJSON PoolEpoch | |
ToJSON PoolHistory | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolHistory -> Value # toEncoding :: PoolHistory -> Encoding # toJSONList :: [PoolHistory] -> Value # toEncodingList :: [PoolHistory] -> Encoding # omitField :: PoolHistory -> Bool # | |
ToJSON PoolInfo | |
ToJSON PoolMetadata | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolMetadata -> Value # toEncoding :: PoolMetadata -> Encoding # toJSONList :: [PoolMetadata] -> Value # toEncodingList :: [PoolMetadata] -> Encoding # omitField :: PoolMetadata -> Bool # | |
ToJSON PoolMetadataResponse | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolMetadataResponse -> Value # toEncoding :: PoolMetadataResponse -> Encoding # toJSONList :: [PoolMetadataResponse] -> Value # toEncodingList :: [PoolMetadataResponse] -> Encoding # omitField :: PoolMetadataResponse -> Bool # | |
ToJSON PoolRegistrationAction | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolRegistrationAction -> Value # toEncoding :: PoolRegistrationAction -> Encoding # toJSONList :: [PoolRegistrationAction] -> Value # toEncodingList :: [PoolRegistrationAction] -> Encoding # omitField :: PoolRegistrationAction -> Bool # | |
ToJSON PoolRelay | |
ToJSON PoolUpdate | |
Defined in Blockfrost.Types.Cardano.Pools Methods toJSON :: PoolUpdate -> Value # toEncoding :: PoolUpdate -> Encoding # toJSONList :: [PoolUpdate] -> Value # toEncodingList :: [PoolUpdate] -> Encoding # omitField :: PoolUpdate -> Bool # | |
ToJSON InlineDatum | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: InlineDatum -> Value # toEncoding :: InlineDatum -> Encoding # toJSONList :: [InlineDatum] -> Value # toEncodingList :: [InlineDatum] -> Encoding # omitField :: InlineDatum -> Bool # | |
ToJSON Script | |
ToJSON ScriptCBOR | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptCBOR -> Value # toEncoding :: ScriptCBOR -> Encoding # toJSONList :: [ScriptCBOR] -> Value # toEncodingList :: [ScriptCBOR] -> Encoding # omitField :: ScriptCBOR -> Bool # | |
ToJSON ScriptDatum | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptDatum -> Value # toEncoding :: ScriptDatum -> Encoding # toJSONList :: [ScriptDatum] -> Value # toEncodingList :: [ScriptDatum] -> Encoding # omitField :: ScriptDatum -> Bool # | |
ToJSON ScriptDatumCBOR | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptDatumCBOR -> Value # toEncoding :: ScriptDatumCBOR -> Encoding # toJSONList :: [ScriptDatumCBOR] -> Value # toEncodingList :: [ScriptDatumCBOR] -> Encoding # omitField :: ScriptDatumCBOR -> Bool # | |
ToJSON ScriptJSON | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptJSON -> Value # toEncoding :: ScriptJSON -> Encoding # toJSONList :: [ScriptJSON] -> Value # toEncodingList :: [ScriptJSON] -> Encoding # omitField :: ScriptJSON -> Bool # | |
ToJSON ScriptRedeemer | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptRedeemer -> Value # toEncoding :: ScriptRedeemer -> Encoding # toJSONList :: [ScriptRedeemer] -> Value # toEncodingList :: [ScriptRedeemer] -> Encoding # omitField :: ScriptRedeemer -> Bool # | |
ToJSON ScriptType | |
Defined in Blockfrost.Types.Cardano.Scripts Methods toJSON :: ScriptType -> Value # toEncoding :: ScriptType -> Encoding # toJSONList :: [ScriptType] -> Value # toEncodingList :: [ScriptType] -> Encoding # omitField :: ScriptType -> Bool # | |
ToJSON PoolUpdateMetadata | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: PoolUpdateMetadata -> Value # toEncoding :: PoolUpdateMetadata -> Encoding # toJSONList :: [PoolUpdateMetadata] -> Value # toEncodingList :: [PoolUpdateMetadata] -> Encoding # omitField :: PoolUpdateMetadata -> Bool # | |
ToJSON Pot | |
ToJSON Transaction | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: Transaction -> Value # toEncoding :: Transaction -> Encoding # toJSONList :: [Transaction] -> Value # toEncodingList :: [Transaction] -> Encoding # omitField :: Transaction -> Bool # | |
ToJSON TransactionCBOR | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionCBOR -> Value # toEncoding :: TransactionCBOR -> Encoding # toJSONList :: [TransactionCBOR] -> Value # toEncodingList :: [TransactionCBOR] -> Encoding # omitField :: TransactionCBOR -> Bool # | |
ToJSON TransactionDelegation | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionDelegation -> Value # toEncoding :: TransactionDelegation -> Encoding # toJSONList :: [TransactionDelegation] -> Value # toEncodingList :: [TransactionDelegation] -> Encoding # omitField :: TransactionDelegation -> Bool # | |
ToJSON TransactionMetaCBOR | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionMetaCBOR -> Value # toEncoding :: TransactionMetaCBOR -> Encoding # toJSONList :: [TransactionMetaCBOR] -> Value # toEncodingList :: [TransactionMetaCBOR] -> Encoding # omitField :: TransactionMetaCBOR -> Bool # | |
ToJSON TransactionMetaJSON | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionMetaJSON -> Value # toEncoding :: TransactionMetaJSON -> Encoding # toJSONList :: [TransactionMetaJSON] -> Value # toEncodingList :: [TransactionMetaJSON] -> Encoding # omitField :: TransactionMetaJSON -> Bool # | |
ToJSON TransactionMir | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionMir -> Value # toEncoding :: TransactionMir -> Encoding # toJSONList :: [TransactionMir] -> Value # toEncodingList :: [TransactionMir] -> Encoding # omitField :: TransactionMir -> Bool # | |
ToJSON TransactionPoolRetiring | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionPoolRetiring -> Value # toEncoding :: TransactionPoolRetiring -> Encoding # toJSONList :: [TransactionPoolRetiring] -> Value # | |
ToJSON TransactionPoolUpdate | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionPoolUpdate -> Value # toEncoding :: TransactionPoolUpdate -> Encoding # toJSONList :: [TransactionPoolUpdate] -> Value # toEncodingList :: [TransactionPoolUpdate] -> Encoding # omitField :: TransactionPoolUpdate -> Bool # | |
ToJSON TransactionRedeemer | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionRedeemer -> Value # toEncoding :: TransactionRedeemer -> Encoding # toJSONList :: [TransactionRedeemer] -> Value # toEncodingList :: [TransactionRedeemer] -> Encoding # omitField :: TransactionRedeemer -> Bool # | |
ToJSON TransactionStake | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionStake -> Value # toEncoding :: TransactionStake -> Encoding # toJSONList :: [TransactionStake] -> Value # toEncodingList :: [TransactionStake] -> Encoding # omitField :: TransactionStake -> Bool # | |
ToJSON TransactionUtxos | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionUtxos -> Value # toEncoding :: TransactionUtxos -> Encoding # toJSONList :: [TransactionUtxos] -> Value # toEncodingList :: [TransactionUtxos] -> Encoding # omitField :: TransactionUtxos -> Bool # | |
ToJSON TransactionWithdrawal | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: TransactionWithdrawal -> Value # toEncoding :: TransactionWithdrawal -> Encoding # toJSONList :: [TransactionWithdrawal] -> Value # toEncodingList :: [TransactionWithdrawal] -> Encoding # omitField :: TransactionWithdrawal -> Bool # | |
ToJSON UtxoInput | |
ToJSON UtxoOutput | |
Defined in Blockfrost.Types.Cardano.Transactions Methods toJSON :: UtxoOutput -> Value # toEncoding :: UtxoOutput -> Encoding # toJSONList :: [UtxoOutput] -> Value # toEncodingList :: [UtxoOutput] -> Encoding # omitField :: UtxoOutput -> Bool # | |
ToJSON DerivedAddress | |
Defined in Blockfrost.Types.Cardano.Utils Methods toJSON :: DerivedAddress -> Value # toEncoding :: DerivedAddress -> Encoding # toJSONList :: [DerivedAddress] -> Value # toEncodingList :: [DerivedAddress] -> Encoding # omitField :: DerivedAddress -> Bool # | |
ToJSON TxEval | |
ToJSON TxEvalBudget | |
Defined in Blockfrost.Types.Cardano.Utils Methods toJSON :: TxEvalBudget -> Value # toEncoding :: TxEvalBudget -> Encoding # toJSONList :: [TxEvalBudget] -> Value # toEncodingList :: [TxEvalBudget] -> Encoding # omitField :: TxEvalBudget -> Bool # | |
ToJSON TxEvalFailure | |
Defined in Blockfrost.Types.Cardano.Utils Methods toJSON :: TxEvalFailure -> Value # toEncoding :: TxEvalFailure -> Encoding # toJSONList :: [TxEvalFailure] -> Value # toEncodingList :: [TxEvalFailure] -> Encoding # | |
ToJSON TxEvalInput | |
Defined in Blockfrost.Types.Cardano.Utils Methods toJSON :: TxEvalInput -> Value # toEncoding :: TxEvalInput -> Encoding # toJSONList :: [TxEvalInput] -> Value # toEncodingList :: [TxEvalInput] -> Encoding # omitField :: TxEvalInput -> Bool # | |
ToJSON TxEvalValidator | |
Defined in Blockfrost.Types.Cardano.Utils Methods toJSON :: TxEvalValidator -> Value # toEncoding :: TxEvalValidator -> Encoding # toJSONList :: [TxEvalValidator] -> Value # toEncodingList :: [TxEvalValidator] -> Encoding # omitField :: TxEvalValidator -> Bool # | |
ToJSON Healthy | |
ToJSON Metric | |
ToJSON ServerTime | |
Defined in Blockfrost.Types.Common Methods toJSON :: ServerTime -> Value # toEncoding :: ServerTime -> Encoding # toJSONList :: [ServerTime] -> Value # toEncodingList :: [ServerTime] -> Encoding # omitField :: ServerTime -> Bool # | |
ToJSON URLVersion | |
Defined in Blockfrost.Types.Common Methods toJSON :: URLVersion -> Value # toEncoding :: URLVersion -> Encoding # toJSONList :: [URLVersion] -> Value # toEncodingList :: [URLVersion] -> Encoding # omitField :: URLVersion -> Bool # | |
ToJSON IPFSAdd | |
ToJSON IPFSPin | |
ToJSON IPFSPinChange | |
Defined in Blockfrost.Types.IPFS Methods toJSON :: IPFSPinChange -> Value # toEncoding :: IPFSPinChange -> Encoding # toJSONList :: [IPFSPinChange] -> Value # toEncodingList :: [IPFSPinChange] -> Encoding # omitField :: IPFSPinChange -> Bool # | |
ToJSON PinState | |
ToJSON NutlinkAddress | |
Defined in Blockfrost.Types.NutLink Methods toJSON :: NutlinkAddress -> Value # toEncoding :: NutlinkAddress -> Encoding # toJSONList :: [NutlinkAddress] -> Value # toEncodingList :: [NutlinkAddress] -> Encoding # omitField :: NutlinkAddress -> Bool # | |
ToJSON NutlinkAddressTicker | |
Defined in Blockfrost.Types.NutLink Methods toJSON :: NutlinkAddressTicker -> Value # toEncoding :: NutlinkAddressTicker -> Encoding # toJSONList :: [NutlinkAddressTicker] -> Value # toEncodingList :: [NutlinkAddressTicker] -> Encoding # omitField :: NutlinkAddressTicker -> Bool # | |
ToJSON NutlinkTicker | |
Defined in Blockfrost.Types.NutLink Methods toJSON :: NutlinkTicker -> Value # toEncoding :: NutlinkTicker -> Encoding # toJSONList :: [NutlinkTicker] -> Value # toEncodingList :: [NutlinkTicker] -> Encoding # omitField :: NutlinkTicker -> Bool # | |
ToJSON Address | |
ToJSON Amount | |
ToJSON AmountExtended | |
Defined in Blockfrost.Types.Shared.Amount Methods toJSON :: AmountExtended -> Value # toEncoding :: AmountExtended -> Encoding # toJSONList :: [AmountExtended] -> Value # toEncodingList :: [AmountExtended] -> Encoding # omitField :: AmountExtended -> Bool # | |
ToJSON AssetId | |
ToJSON BlockHash | |
ToJSON CBORString | |
Defined in Blockfrost.Types.Shared.CBOR Methods toJSON :: CBORString -> Value # toEncoding :: CBORString -> Encoding # toJSONList :: [CBORString] -> Value # toEncodingList :: [CBORString] -> Encoding # omitField :: CBORString -> Bool # | |
ToJSON DatumHash | |
ToJSON Epoch | |
ToJSON EpochLength | |
Defined in Blockfrost.Types.Shared.Epoch Methods toJSON :: EpochLength -> Value # toEncoding :: EpochLength -> Encoding # toJSONList :: [EpochLength] -> Value # toEncodingList :: [EpochLength] -> Encoding # omitField :: EpochLength -> Bool # | |
ToJSON POSIXMillis | |
Defined in Blockfrost.Types.Shared.POSIXMillis Methods toJSON :: POSIXMillis -> Value # toEncoding :: POSIXMillis -> Encoding # toJSONList :: [POSIXMillis] -> Value # toEncodingList :: [POSIXMillis] -> Encoding # omitField :: POSIXMillis -> Bool # | |
ToJSON PolicyId | |
ToJSON PoolId | |
ToJSON Quantity | |
ToJSON ScriptHash | |
Defined in Blockfrost.Types.Shared.ScriptHash Methods toJSON :: ScriptHash -> Value # toEncoding :: ScriptHash -> Encoding # toJSONList :: [ScriptHash] -> Value # toEncodingList :: [ScriptHash] -> Encoding # omitField :: ScriptHash -> Bool # | |
ToJSON ScriptHashList | |
Defined in Blockfrost.Types.Shared.ScriptHash Methods toJSON :: ScriptHashList -> Value # toEncoding :: ScriptHashList -> Encoding # toJSONList :: [ScriptHashList] -> Value # toEncodingList :: [ScriptHashList] -> Encoding # omitField :: ScriptHashList -> Bool # | |
ToJSON Slot | |
ToJSON TxHash | |
ToJSON TxHashObject | |
Defined in Blockfrost.Types.Shared.TxHash Methods toJSON :: TxHashObject -> Value # toEncoding :: TxHashObject -> Encoding # toJSONList :: [TxHashObject] -> Value # toEncodingList :: [TxHashObject] -> Encoding # omitField :: TxHashObject -> Bool # | |
ToJSON ValidationPurpose | |
Defined in Blockfrost.Types.Shared.ValidationPurpose Methods toJSON :: ValidationPurpose -> Value # toEncoding :: ValidationPurpose -> Encoding # toJSONList :: [ValidationPurpose] -> Value # toEncodingList :: [ValidationPurpose] -> Encoding # omitField :: ValidationPurpose -> Bool # | |
(TypeError ('Text "Forbidden ToJSON ByteString instance") :: Constraint) => ToJSON ByteString # | |
Defined in GeniusYield.Imports Methods toJSON :: ByteString -> Value # toEncoding :: ByteString -> Encoding # toJSONList :: [ByteString] -> Value # toEncodingList :: [ByteString] -> Encoding # omitField :: ByteString -> Bool # | |
ToJSON ChainPointer | |
Defined in Cardano.Address Methods toJSON :: ChainPointer -> Value # toEncoding :: ChainPointer -> Encoding # toJSONList :: [ChainPointer] -> Value # toEncodingList :: [ChainPointer] -> Encoding # omitField :: ChainPointer -> Bool # | |
ToJSON NetworkTag | |
Defined in Cardano.Address Methods toJSON :: NetworkTag -> Value # toEncoding :: NetworkTag -> Encoding # toJSONList :: [NetworkTag] -> Value # toEncodingList :: [NetworkTag] -> Encoding # omitField :: NetworkTag -> Bool # | |
ToJSON KeyHash | |
ToJSON Cosigner | |
ToJSON ScriptTemplate | |
Defined in Cardano.Address.Script Methods toJSON :: ScriptTemplate -> Value # toEncoding :: ScriptTemplate -> Encoding # toJSONList :: [ScriptTemplate] -> Value # toEncodingList :: [ScriptTemplate] -> Encoding # omitField :: ScriptTemplate -> Bool # | |
ToJSON AddressInfo | |
Defined in Cardano.Address.Style.Byron Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |
ToJSON ErrInspectAddress | |
Defined in Cardano.Address.Style.Byron Methods toJSON :: ErrInspectAddress -> Value # toEncoding :: ErrInspectAddress -> Encoding # toJSONList :: [ErrInspectAddress] -> Value # toEncodingList :: [ErrInspectAddress] -> Encoding # omitField :: ErrInspectAddress -> Bool # | |
ToJSON PayloadInfo | |
Defined in Cardano.Address.Style.Byron Methods toJSON :: PayloadInfo -> Value # toEncoding :: PayloadInfo -> Encoding # toJSONList :: [PayloadInfo] -> Value # toEncodingList :: [PayloadInfo] -> Encoding # | |
ToJSON AddressInfo | |
Defined in Cardano.Address.Style.Icarus Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |
ToJSON ErrInspectAddress | |
Defined in Cardano.Address.Style.Icarus Methods toJSON :: ErrInspectAddress -> Value # toEncoding :: ErrInspectAddress -> Encoding # toJSONList :: [ErrInspectAddress] -> Value # toEncodingList :: [ErrInspectAddress] -> Encoding # omitField :: ErrInspectAddress -> Bool # | |
ToJSON AddressInfo | |
Defined in Cardano.Address.Style.Shelley Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |
ToJSON ErrInspectAddress | |
Defined in Cardano.Address.Style.Shelley Methods toJSON :: ErrInspectAddress -> Value # toEncoding :: ErrInspectAddress -> Encoding # toJSONList :: [ErrInspectAddress] -> Value # toEncodingList :: [ErrInspectAddress] -> Encoding # omitField :: ErrInspectAddress -> Bool # | |
ToJSON ErrInspectAddressOnlyShelley | |
Defined in Cardano.Address.Style.Shelley Methods toJSON :: ErrInspectAddressOnlyShelley -> Value # toEncoding :: ErrInspectAddressOnlyShelley -> Encoding # toJSONList :: [ErrInspectAddressOnlyShelley] -> Value # toEncodingList :: [ErrInspectAddressOnlyShelley] -> Encoding # | |
ToJSON InspectAddress | |
Defined in Cardano.Address.Style.Shelley Methods toJSON :: InspectAddress -> Value # toEncoding :: InspectAddress -> Encoding # toJSONList :: [InspectAddress] -> Value # toEncodingList :: [InspectAddress] -> Encoding # omitField :: InspectAddress -> Bool # | |
ToJSON StakeAddress | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeAddress -> Value # toEncoding :: StakeAddress -> Encoding # toJSONList :: [StakeAddress] -> Value # toEncodingList :: [StakeAddress] -> Encoding # omitField :: StakeAddress -> Bool # | |
ToJSON StakeCredential | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeCredential -> Value # toEncoding :: StakeCredential -> Encoding # toJSONList :: [StakeCredential] -> Value # toEncodingList :: [StakeCredential] -> Encoding # omitField :: StakeCredential -> Bool # | |
ToJSON ChainPoint | |
Defined in Cardano.Api.Internal.Block Methods toJSON :: ChainPoint -> Value # toEncoding :: ChainPoint -> Encoding # toJSONList :: [ChainPoint] -> Value # toEncodingList :: [ChainPoint] -> Encoding # omitField :: ChainPoint -> Bool # | |
ToJSON ChainTip | |
ToJSON AnyShelleyBasedEra | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toJSON :: AnyShelleyBasedEra -> Value # toEncoding :: AnyShelleyBasedEra -> Encoding # toJSONList :: [AnyShelleyBasedEra] -> Value # toEncodingList :: [AnyShelleyBasedEra] -> Encoding # omitField :: AnyShelleyBasedEra -> Bool # | |
ToJSON AnyCardanoEra | |
Defined in Cardano.Api.Internal.Eras.Core Methods toJSON :: AnyCardanoEra -> Value # toEncoding :: AnyCardanoEra -> Encoding # toJSONList :: [AnyCardanoEra] -> Value # toEncodingList :: [AnyCardanoEra] -> Encoding # omitField :: AnyCardanoEra -> Bool # | |
ToJSON LocalTxMonitoringResult | |
Defined in Cardano.Api.Internal.IPC Methods toJSON :: LocalTxMonitoringResult -> Value # toEncoding :: LocalTxMonitoringResult -> Encoding # toJSONList :: [LocalTxMonitoringResult] -> Value # | |
ToJSON TxValidationErrorInCardanoMode | |
Defined in Cardano.Api.Internal.InMode | |
ToJSON CostModels | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: CostModels -> Value # toEncoding :: CostModels -> Encoding # toJSONList :: [CostModels] -> Value # toEncodingList :: [CostModels] -> Encoding # omitField :: CostModels -> Bool # | |
ToJSON ExecutionUnitPrices | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: ExecutionUnitPrices -> Value # toEncoding :: ExecutionUnitPrices -> Encoding # toJSONList :: [ExecutionUnitPrices] -> Value # toEncodingList :: [ExecutionUnitPrices] -> Encoding # omitField :: ExecutionUnitPrices -> Bool # | |
ToJSON PraosNonce | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: PraosNonce -> Value # toEncoding :: PraosNonce -> Encoding # toJSONList :: [PraosNonce] -> Value # toEncodingList :: [PraosNonce] -> Encoding # omitField :: PraosNonce -> Bool # | |
ToJSON ProtocolParameters | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: ProtocolParameters -> Value # toEncoding :: ProtocolParameters -> Encoding # toJSONList :: [ProtocolParameters] -> Value # toEncodingList :: [ProtocolParameters] -> Encoding # | |
ToJSON AnyPlutusScriptVersion | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: AnyPlutusScriptVersion -> Value # toEncoding :: AnyPlutusScriptVersion -> Encoding # toJSONList :: [AnyPlutusScriptVersion] -> Value # toEncodingList :: [AnyPlutusScriptVersion] -> Encoding # omitField :: AnyPlutusScriptVersion -> Bool # | |
ToJSON ExecutionUnits | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ExecutionUnits -> Value # toEncoding :: ExecutionUnits -> Encoding # toJSONList :: [ExecutionUnits] -> Value # toEncodingList :: [ExecutionUnits] -> Encoding # omitField :: ExecutionUnits -> Bool # | |
ToJSON ScriptHash | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptHash -> Value # toEncoding :: ScriptHash -> Encoding # toJSONList :: [ScriptHash] -> Value # toEncodingList :: [ScriptHash] -> Encoding # omitField :: ScriptHash -> Bool # | |
ToJSON ScriptInAnyLang | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptInAnyLang -> Value # toEncoding :: ScriptInAnyLang -> Encoding # toJSONList :: [ScriptInAnyLang] -> Value # toEncodingList :: [ScriptInAnyLang] -> Encoding # omitField :: ScriptInAnyLang -> Bool # | |
ToJSON SimpleScript | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: SimpleScript -> Value # toEncoding :: SimpleScript -> Encoding # toJSONList :: [SimpleScript] -> Value # toEncodingList :: [SimpleScript] -> Encoding # omitField :: SimpleScript -> Bool # | |
ToJSON TextEnvelope | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods toJSON :: TextEnvelope -> Value # toEncoding :: TextEnvelope -> Encoding # toJSONList :: [TextEnvelope] -> Value # toEncodingList :: [TextEnvelope] -> Encoding # omitField :: TextEnvelope -> Bool # | |
ToJSON TextEnvelopeDescr | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods toJSON :: TextEnvelopeDescr -> Value # toEncoding :: TextEnvelopeDescr -> Encoding # toJSONList :: [TextEnvelopeDescr] -> Value # toEncodingList :: [TextEnvelopeDescr] -> Encoding # omitField :: TextEnvelopeDescr -> Bool # | |
ToJSON TextEnvelopeType | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods toJSON :: TextEnvelopeType -> Value # toEncoding :: TextEnvelopeType -> Encoding # toJSONList :: [TextEnvelopeType] -> Value # toEncodingList :: [TextEnvelopeType] -> Encoding # omitField :: TextEnvelopeType -> Bool # | |
ToJSON ScriptWitnessIndex | |
Defined in Cardano.Api.Internal.Tx.Body Methods toJSON :: ScriptWitnessIndex -> Value # toEncoding :: ScriptWitnessIndex -> Encoding # toJSONList :: [ScriptWitnessIndex] -> Value # toEncodingList :: [ScriptWitnessIndex] -> Encoding # omitField :: ScriptWitnessIndex -> Bool # | |
ToJSON TxId | |
ToJSON TxIn | |
ToJSON TxIx | |
ToJSON AssetName | |
ToJSON PolicyId | |
ToJSON Quantity | |
ToJSON Value | |
ToJSON ValueNestedRep | |
Defined in Cardano.Api.Internal.Value Methods toJSON :: ValueNestedRep -> Value # toEncoding :: ValueNestedRep -> Encoding # toJSONList :: [ValueNestedRep] -> Value # toEncodingList :: [ValueNestedRep] -> Encoding # omitField :: ValueNestedRep -> Bool # | |
ToJSON ProtocolMagic | |
Defined in Cardano.Crypto.ProtocolMagic Methods toJSON :: ProtocolMagic -> Value # toEncoding :: ProtocolMagic -> Encoding # toJSONList :: [ProtocolMagic] -> Value # toEncodingList :: [ProtocolMagic] -> Encoding # omitField :: ProtocolMagic -> Bool # | |
ToJSON ProtocolMagicId | |
Defined in Cardano.Crypto.ProtocolMagic Methods toJSON :: ProtocolMagicId -> Value # toEncoding :: ProtocolMagicId -> Encoding # toJSONList :: [ProtocolMagicId] -> Value # toEncodingList :: [ProtocolMagicId] -> Encoding # omitField :: ProtocolMagicId -> Bool # | |
ToJSON RequiresNetworkMagic | |
Defined in Cardano.Crypto.ProtocolMagic Methods toJSON :: RequiresNetworkMagic -> Value # toEncoding :: RequiresNetworkMagic -> Encoding # toJSONList :: [RequiresNetworkMagic] -> Value # toEncodingList :: [RequiresNetworkMagic] -> Encoding # omitField :: RequiresNetworkMagic -> Bool # | |
ToJSON CompactRedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.Compact Methods toJSON :: CompactRedeemVerificationKey -> Value # toEncoding :: CompactRedeemVerificationKey -> Encoding # toJSONList :: [CompactRedeemVerificationKey] -> Value # toEncodingList :: [CompactRedeemVerificationKey] -> Encoding # | |
ToJSON RedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.VerificationKey Methods toJSON :: RedeemVerificationKey -> Value # toEncoding :: RedeemVerificationKey -> Encoding # toJSONList :: [RedeemVerificationKey] -> Value # toEncodingList :: [RedeemVerificationKey] -> Encoding # omitField :: RedeemVerificationKey -> Bool # | |
ToJSON VerificationKey | |
Defined in Cardano.Crypto.Signing.VerificationKey Methods toJSON :: VerificationKey -> Value # toEncoding :: VerificationKey -> Encoding # toJSONList :: [VerificationKey] -> Value # toEncodingList :: [VerificationKey] -> Encoding # omitField :: VerificationKey -> Bool # | |
ToJSON ValidityInterval | |
Defined in Cardano.Ledger.Allegra.Scripts Methods toJSON :: ValidityInterval -> Value # toEncoding :: ValidityInterval -> Encoding # toJSONList :: [ValidityInterval] -> Value # toEncodingList :: [ValidityInterval] -> Encoding # omitField :: ValidityInterval -> Bool # | |
ToJSON AlonzoGenesis | |
Defined in Cardano.Ledger.Alonzo.Genesis Methods toJSON :: AlonzoGenesis -> Value # toEncoding :: AlonzoGenesis -> Encoding # toJSONList :: [AlonzoGenesis] -> Value # toEncodingList :: [AlonzoGenesis] -> Encoding # omitField :: AlonzoGenesis -> Bool # | |
ToJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: CoinPerWord -> Value # toEncoding :: CoinPerWord -> Encoding # toJSONList :: [CoinPerWord] -> Value # toEncodingList :: [CoinPerWord] -> Encoding # omitField :: CoinPerWord -> Bool # | |
ToJSON OrdExUnits | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: OrdExUnits -> Value # toEncoding :: OrdExUnits -> Encoding # toJSONList :: [OrdExUnits] -> Value # toEncodingList :: [OrdExUnits] -> Encoding # omitField :: OrdExUnits -> Bool # | |
ToJSON FailureDescription | |
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Methods toJSON :: FailureDescription -> Value # toEncoding :: FailureDescription -> Encoding # toJSONList :: [FailureDescription] -> Value # toEncodingList :: [FailureDescription] -> Encoding # omitField :: FailureDescription -> Bool # | |
ToJSON TagMismatchDescription | |
Defined in Cardano.Ledger.Alonzo.Rules.Utxos Methods toJSON :: TagMismatchDescription -> Value # toEncoding :: TagMismatchDescription -> Encoding # toJSONList :: [TagMismatchDescription] -> Value # toEncodingList :: [TagMismatchDescription] -> Encoding # omitField :: TagMismatchDescription -> Bool # | |
ToJSON IsValid | |
ToJSON CommitteeMemberState | |
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: CommitteeMemberState -> Value # toEncoding :: CommitteeMemberState -> Encoding # toJSONList :: [CommitteeMemberState] -> Value # toEncodingList :: [CommitteeMemberState] -> Encoding # omitField :: CommitteeMemberState -> Bool # | |
ToJSON CommitteeMembersState | |
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: CommitteeMembersState -> Value # toEncoding :: CommitteeMembersState -> Encoding # toJSONList :: [CommitteeMembersState] -> Value # toEncodingList :: [CommitteeMembersState] -> Encoding # omitField :: CommitteeMembersState -> Bool # | |
ToJSON HotCredAuthStatus | |
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: HotCredAuthStatus -> Value # toEncoding :: HotCredAuthStatus -> Encoding # toJSONList :: [HotCredAuthStatus] -> Value # toEncodingList :: [HotCredAuthStatus] -> Encoding # omitField :: HotCredAuthStatus -> Bool # | |
ToJSON MemberStatus | |
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: MemberStatus -> Value # toEncoding :: MemberStatus -> Encoding # toJSONList :: [MemberStatus] -> Value # toEncodingList :: [MemberStatus] -> Encoding # omitField :: MemberStatus -> Bool # | |
ToJSON NextEpochChange | |
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: NextEpochChange -> Value # toEncoding :: NextEpochChange -> Encoding # toJSONList :: [NextEpochChange] -> Value # toEncodingList :: [NextEpochChange] -> Encoding # omitField :: NextEpochChange -> Bool # | |
ToJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: CoinPerByte -> Value # toEncoding :: CoinPerByte -> Encoding # toJSONList :: [CoinPerByte] -> Value # toEncodingList :: [CoinPerByte] -> Encoding # omitField :: CoinPerByte -> Bool # | |
ToJSON ByteSpan | |
ToJSON Version | |
ToJSON Proof | |
ToJSON AddrAttributes | |
Defined in Cardano.Chain.Common.AddrAttributes Methods toJSON :: AddrAttributes -> Value # toEncoding :: AddrAttributes -> Encoding # toJSONList :: [AddrAttributes] -> Value # toEncodingList :: [AddrAttributes] -> Encoding # omitField :: AddrAttributes -> Bool # | |
ToJSON HDAddressPayload | |
Defined in Cardano.Chain.Common.AddrAttributes Methods toJSON :: HDAddressPayload -> Value # toEncoding :: HDAddressPayload -> Encoding # toJSONList :: [HDAddressPayload] -> Value # toEncodingList :: [HDAddressPayload] -> Encoding # omitField :: HDAddressPayload -> Bool # | |
ToJSON AddrType | |
ToJSON Address | |
ToJSON UnparsedFields | |
Defined in Cardano.Chain.Common.Attributes Methods toJSON :: UnparsedFields -> Value # toEncoding :: UnparsedFields -> Encoding # toJSONList :: [UnparsedFields] -> Value # toEncodingList :: [UnparsedFields] -> Encoding # omitField :: UnparsedFields -> Bool # | |
ToJSON ChainDifficulty | |
Defined in Cardano.Chain.Common.ChainDifficulty Methods toJSON :: ChainDifficulty -> Value # toEncoding :: ChainDifficulty -> Encoding # toJSONList :: [ChainDifficulty] -> Value # toEncodingList :: [ChainDifficulty] -> Encoding # omitField :: ChainDifficulty -> Bool # | |
ToJSON Lovelace | |
ToJSON LovelacePortion | |
Defined in Cardano.Chain.Common.LovelacePortion Methods toJSON :: LovelacePortion -> Value # toEncoding :: LovelacePortion -> Encoding # toJSONList :: [LovelacePortion] -> Value # toEncodingList :: [LovelacePortion] -> Encoding # omitField :: LovelacePortion -> Bool # | |
ToJSON NetworkMagic | |
Defined in Cardano.Chain.Common.NetworkMagic Methods toJSON :: NetworkMagic -> Value # toEncoding :: NetworkMagic -> Encoding # toJSONList :: [NetworkMagic] -> Value # toEncodingList :: [NetworkMagic] -> Encoding # omitField :: NetworkMagic -> Bool # | |
ToJSON TxFeePolicy | |
Defined in Cardano.Chain.Common.TxFeePolicy Methods toJSON :: TxFeePolicy -> Value # toEncoding :: TxFeePolicy -> Encoding # toJSONList :: [TxFeePolicy] -> Value # toEncodingList :: [TxFeePolicy] -> Encoding # omitField :: TxFeePolicy -> Bool # | |
ToJSON TxSizeLinear | |
Defined in Cardano.Chain.Common.TxSizeLinear Methods toJSON :: TxSizeLinear -> Value # toEncoding :: TxSizeLinear -> Encoding # toJSONList :: [TxSizeLinear] -> Value # toEncodingList :: [TxSizeLinear] -> Encoding # omitField :: TxSizeLinear -> Bool # | |
ToJSON GenesisHash | |
Defined in Cardano.Chain.Genesis.Hash Methods toJSON :: GenesisHash -> Value # toEncoding :: GenesisHash -> Encoding # toJSONList :: [GenesisHash] -> Value # toEncodingList :: [GenesisHash] -> Encoding # omitField :: GenesisHash -> Bool # | |
ToJSON EpochNumber | |
Defined in Cardano.Chain.Slotting.EpochNumber Methods toJSON :: EpochNumber -> Value # toEncoding :: EpochNumber -> Encoding # toJSONList :: [EpochNumber] -> Value # toEncodingList :: [EpochNumber] -> Encoding # omitField :: EpochNumber -> Bool # | |
ToJSON SlotNumber | |
Defined in Cardano.Chain.Slotting.SlotNumber Methods toJSON :: SlotNumber -> Value # toEncoding :: SlotNumber -> Encoding # toJSONList :: [SlotNumber] -> Value # toEncodingList :: [SlotNumber] -> Encoding # omitField :: SlotNumber -> Bool # | |
ToJSON SscPayload | |
Defined in Cardano.Chain.Ssc Methods toJSON :: SscPayload -> Value # toEncoding :: SscPayload -> Encoding # toJSONList :: [SscPayload] -> Value # toEncodingList :: [SscPayload] -> Encoding # omitField :: SscPayload -> Bool # | |
ToJSON SscProof | |
ToJSON Tx | |
ToJSON TxIn | |
ToJSON TxOut | |
ToJSON TxProof | |
ToJSON TxInWitness | |
Defined in Cardano.Chain.UTxO.TxWitness Methods toJSON :: TxInWitness -> Value # toEncoding :: TxInWitness -> Encoding # toJSONList :: [TxInWitness] -> Value # toEncodingList :: [TxInWitness] -> Encoding # omitField :: TxInWitness -> Bool # | |
ToJSON TxSigData | |
ToJSON ApplicationName | |
Defined in Cardano.Chain.Update.ApplicationName Methods toJSON :: ApplicationName -> Value # toEncoding :: ApplicationName -> Encoding # toJSONList :: [ApplicationName] -> Value # toEncodingList :: [ApplicationName] -> Encoding # omitField :: ApplicationName -> Bool # | |
ToJSON InstallerHash | |
Defined in Cardano.Chain.Update.InstallerHash Methods toJSON :: InstallerHash -> Value # toEncoding :: InstallerHash -> Encoding # toJSONList :: [InstallerHash] -> Value # toEncodingList :: [InstallerHash] -> Encoding # omitField :: InstallerHash -> Bool # | |
ToJSON ProposalBody | |
Defined in Cardano.Chain.Update.Proposal Methods toJSON :: ProposalBody -> Value # toEncoding :: ProposalBody -> Encoding # toJSONList :: [ProposalBody] -> Value # toEncodingList :: [ProposalBody] -> Encoding # omitField :: ProposalBody -> Bool # | |
ToJSON ProtocolParametersUpdate | |
Defined in Cardano.Chain.Update.ProtocolParametersUpdate Methods toJSON :: ProtocolParametersUpdate -> Value # toEncoding :: ProtocolParametersUpdate -> Encoding # toJSONList :: [ProtocolParametersUpdate] -> Value # | |
ToJSON ProtocolVersion | |
Defined in Cardano.Chain.Update.ProtocolVersion Methods toJSON :: ProtocolVersion -> Value # toEncoding :: ProtocolVersion -> Encoding # toJSONList :: [ProtocolVersion] -> Value # toEncodingList :: [ProtocolVersion] -> Encoding # omitField :: ProtocolVersion -> Bool # | |
ToJSON SoftforkRule | |
Defined in Cardano.Chain.Update.SoftforkRule Methods toJSON :: SoftforkRule -> Value # toEncoding :: SoftforkRule -> Encoding # toJSONList :: [SoftforkRule] -> Value # toEncodingList :: [SoftforkRule] -> Encoding # omitField :: SoftforkRule -> Bool # | |
ToJSON SoftwareVersion | |
Defined in Cardano.Chain.Update.SoftwareVersion Methods toJSON :: SoftwareVersion -> Value # toEncoding :: SoftwareVersion -> Encoding # toJSONList :: [SoftwareVersion] -> Value # toEncodingList :: [SoftwareVersion] -> Encoding # omitField :: SoftwareVersion -> Bool # | |
ToJSON SystemTag | |
ToJSON ConwayGenesis | |
Defined in Cardano.Ledger.Conway.Genesis Methods toJSON :: ConwayGenesis -> Value # toEncoding :: ConwayGenesis -> Encoding # toJSONList :: [ConwayGenesis] -> Value # toEncodingList :: [ConwayGenesis] -> Encoding # omitField :: ConwayGenesis -> Bool # | |
ToJSON GovActionId | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionId -> Value # toEncoding :: GovActionId -> Encoding # toJSONList :: [GovActionId] -> Value # toEncodingList :: [GovActionId] -> Encoding # omitField :: GovActionId -> Bool # | |
ToJSON GovActionIx | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionIx -> Value # toEncoding :: GovActionIx -> Encoding # toJSONList :: [GovActionIx] -> Value # toEncodingList :: [GovActionIx] -> Encoding # omitField :: GovActionIx -> Bool # | |
ToJSON Vote | |
ToJSON Voter | |
ToJSON DRepVotingThresholds | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: DRepVotingThresholds -> Value # toEncoding :: DRepVotingThresholds -> Encoding # toJSONList :: [DRepVotingThresholds] -> Value # toEncodingList :: [DRepVotingThresholds] -> Encoding # omitField :: DRepVotingThresholds -> Bool # | |
ToJSON PoolVotingThresholds | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: PoolVotingThresholds -> Value # toEncoding :: PoolVotingThresholds -> Encoding # toJSONList :: [PoolVotingThresholds] -> Value # toEncodingList :: [PoolVotingThresholds] -> Encoding # omitField :: PoolVotingThresholds -> Bool # | |
ToJSON ConwayDelegCert | |
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayDelegCert -> Value # toEncoding :: ConwayDelegCert -> Encoding # toJSONList :: [ConwayDelegCert] -> Value # toEncodingList :: [ConwayDelegCert] -> Encoding # omitField :: ConwayDelegCert -> Bool # | |
ToJSON ConwayGovCert | |
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayGovCert -> Value # toEncoding :: ConwayGovCert -> Encoding # toJSONList :: [ConwayGovCert] -> Value # toEncodingList :: [ConwayGovCert] -> Encoding # omitField :: ConwayGovCert -> Bool # | |
ToJSON Delegatee | |
ToJSON Addr | |
ToJSON RewardAccount | |
Defined in Cardano.Ledger.Address Methods toJSON :: RewardAccount -> Value # toEncoding :: RewardAccount -> Encoding # toJSONList :: [RewardAccount] -> Value # toEncodingList :: [RewardAccount] -> Encoding # omitField :: RewardAccount -> Bool # | |
ToJSON Anchor | |
ToJSON BlocksMade | |
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: BlocksMade -> Value # toEncoding :: BlocksMade -> Encoding # toJSONList :: [BlocksMade] -> Value # toEncodingList :: [BlocksMade] -> Encoding # omitField :: BlocksMade -> Bool # | |
ToJSON CertIx | |
ToJSON DnsName | |
ToJSON Network | |
ToJSON NonNegativeInterval | |
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: NonNegativeInterval -> Value # toEncoding :: NonNegativeInterval -> Encoding # toJSONList :: [NonNegativeInterval] -> Value # toEncodingList :: [NonNegativeInterval] -> Encoding # omitField :: NonNegativeInterval -> Bool # | |
ToJSON Nonce | |
ToJSON Port | |
ToJSON PositiveInterval | |
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: PositiveInterval -> Value # toEncoding :: PositiveInterval -> Encoding # toJSONList :: [PositiveInterval] -> Value # toEncodingList :: [PositiveInterval] -> Encoding # omitField :: PositiveInterval -> Bool # | |
ToJSON PositiveUnitInterval | |
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: PositiveUnitInterval -> Value # toEncoding :: PositiveUnitInterval -> Encoding # toJSONList :: [PositiveUnitInterval] -> Value # toEncodingList :: [PositiveUnitInterval] -> Encoding # omitField :: PositiveUnitInterval -> Bool # | |
ToJSON ProtVer | |
ToJSON Relation | |
ToJSON TxIx | |
ToJSON UnitInterval | |
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: UnitInterval -> Value # toEncoding :: UnitInterval -> Encoding # toJSONList :: [UnitInterval] -> Value # toEncodingList :: [UnitInterval] -> Encoding # omitField :: UnitInterval -> Bool # | |
ToJSON Url | |
ToJSON CommitteeAuthorization | |
Defined in Cardano.Ledger.CertState Methods toJSON :: CommitteeAuthorization -> Value # toEncoding :: CommitteeAuthorization -> Encoding # toJSONList :: [CommitteeAuthorization] -> Value # toEncodingList :: [CommitteeAuthorization] -> Encoding # omitField :: CommitteeAuthorization -> Bool # | |
ToJSON FutureGenDeleg | |
Defined in Cardano.Ledger.CertState Methods toJSON :: FutureGenDeleg -> Value # toEncoding :: FutureGenDeleg -> Encoding # toJSONList :: [FutureGenDeleg] -> Value # toEncodingList :: [FutureGenDeleg] -> Encoding # omitField :: FutureGenDeleg -> Bool # | |
ToJSON InstantaneousRewards | |
Defined in Cardano.Ledger.CertState Methods toJSON :: InstantaneousRewards -> Value # toEncoding :: InstantaneousRewards -> Encoding # toJSONList :: [InstantaneousRewards] -> Value # toEncodingList :: [InstantaneousRewards] -> Encoding # omitField :: InstantaneousRewards -> Bool # | |
ToJSON Coin | |
ToJSON DeltaCoin | |
ToJSON PoolCert | |
ToJSON Ptr | |
ToJSON SlotNo32 | |
ToJSON StakeReference | |
Defined in Cardano.Ledger.Credential Methods toJSON :: StakeReference -> Value # toEncoding :: StakeReference -> Encoding # toJSONList :: [StakeReference] -> Value # toEncodingList :: [StakeReference] -> Encoding # omitField :: StakeReference -> Bool # | |
ToJSON DRep | |
ToJSON DRepState | |
ToJSON GenDelegPair | |
Defined in Cardano.Ledger.Hashes Methods toJSON :: GenDelegPair -> Value # toEncoding :: GenDelegPair -> Encoding # toJSONList :: [GenDelegPair] -> Value # toEncodingList :: [GenDelegPair] -> Encoding # omitField :: GenDelegPair -> Bool # | |
ToJSON GenDelegs | |
ToJSON ScriptHash | |
Defined in Cardano.Ledger.Hashes Methods toJSON :: ScriptHash -> Value # toEncoding :: ScriptHash -> Encoding # toJSONList :: [ScriptHash] -> Value # toEncodingList :: [ScriptHash] -> Encoding # omitField :: ScriptHash -> Bool # | |
ToJSON TxAuxDataHash | |
Defined in Cardano.Ledger.Hashes Methods toJSON :: TxAuxDataHash -> Value # toEncoding :: TxAuxDataHash -> Encoding # toJSONList :: [TxAuxDataHash] -> Value # toEncodingList :: [TxAuxDataHash] -> Encoding # omitField :: TxAuxDataHash -> Bool # | |
ToJSON CostModel | |
ToJSON CostModels | |
Defined in Cardano.Ledger.Plutus.CostModels Methods toJSON :: CostModels -> Value # toEncoding :: CostModels -> Encoding # toJSONList :: [CostModels] -> Value # toEncodingList :: [CostModels] -> Encoding # omitField :: CostModels -> Bool # | |
ToJSON ExUnits | |
ToJSON Prices | |
ToJSON Language | |
ToJSON TxOutSource | |
Defined in Cardano.Ledger.Plutus.TxInfo Methods toJSON :: TxOutSource -> Value # toEncoding :: TxOutSource -> Encoding # toJSONList :: [TxOutSource] -> Value # toEncodingList :: [TxOutSource] -> Encoding # omitField :: TxOutSource -> Bool # | |
ToJSON PoolMetadata | |
Defined in Cardano.Ledger.PoolParams Methods toJSON :: PoolMetadata -> Value # toEncoding :: PoolMetadata -> Encoding # toJSONList :: [PoolMetadata] -> Value # toEncodingList :: [PoolMetadata] -> Encoding # omitField :: PoolMetadata -> Bool # | |
ToJSON PoolParams | |
Defined in Cardano.Ledger.PoolParams Methods toJSON :: PoolParams -> Value # toEncoding :: PoolParams -> Encoding # toJSONList :: [PoolParams] -> Value # toEncodingList :: [PoolParams] -> Encoding # omitField :: PoolParams -> Bool # | |
ToJSON StakePoolRelay | |
Defined in Cardano.Ledger.PoolParams Methods toJSON :: StakePoolRelay -> Value # toEncoding :: StakePoolRelay -> Encoding # toJSONList :: [StakePoolRelay] -> Value # toEncodingList :: [StakePoolRelay] -> Encoding # omitField :: StakePoolRelay -> Bool # | |
ToJSON Reward | |
ToJSON RewardType | |
Defined in Cardano.Ledger.Rewards Methods toJSON :: RewardType -> Value # toEncoding :: RewardType -> Encoding # toJSONList :: [RewardType] -> Value # toEncodingList :: [RewardType] -> Encoding # omitField :: RewardType -> Bool # | |
ToJSON AccountState | |
Defined in Cardano.Ledger.State.AccountState Methods toJSON :: AccountState -> Value # toEncoding :: AccountState -> Encoding # toJSONList :: [AccountState] -> Value # toEncodingList :: [AccountState] -> Encoding # omitField :: AccountState -> Bool # | |
ToJSON IndividualPoolStake | |
Defined in Cardano.Ledger.State.PoolDistr Methods toJSON :: IndividualPoolStake -> Value # toEncoding :: IndividualPoolStake -> Encoding # toJSONList :: [IndividualPoolStake] -> Value # toEncodingList :: [IndividualPoolStake] -> Encoding # omitField :: IndividualPoolStake -> Bool # | |
ToJSON PoolDistr | |
ToJSON SnapShot | |
ToJSON SnapShots | |
ToJSON Stake | |
ToJSON TxId | |
ToJSON TxIn | |
ToJSON UMElem | |
ToJSON UMap | |
ToJSON AssetName | |
ToJSON MaryValue | |
ToJSON MultiAsset | |
Defined in Cardano.Ledger.Mary.Value Methods toJSON :: MultiAsset -> Value # toEncoding :: MultiAsset -> Encoding # toJSONList :: [MultiAsset] -> Value # toEncodingList :: [MultiAsset] -> Encoding # omitField :: MultiAsset -> Bool # | |
ToJSON PolicyID | |
ToJSON RewardInfoPool | |
Defined in Cardano.Ledger.Shelley.API.Wallet Methods toJSON :: RewardInfoPool -> Value # toEncoding :: RewardInfoPool -> Encoding # toJSONList :: [RewardInfoPool] -> Value # toEncodingList :: [RewardInfoPool] -> Encoding # omitField :: RewardInfoPool -> Bool # | |
ToJSON RewardParams | |
Defined in Cardano.Ledger.Shelley.API.Wallet Methods toJSON :: RewardParams -> Value # toEncoding :: RewardParams -> Encoding # toJSONList :: [RewardParams] -> Value # toEncodingList :: [RewardParams] -> Encoding # omitField :: RewardParams -> Bool # | |
ToJSON LegacyJSONPParams | |
Defined in Cardano.Ledger.Shelley.Genesis Methods toJSON :: LegacyJSONPParams -> Value # toEncoding :: LegacyJSONPParams -> Encoding # toJSONList :: [LegacyJSONPParams] -> Value # toEncodingList :: [LegacyJSONPParams] -> Encoding # | |
ToJSON NominalDiffTimeMicro | |
Defined in Cardano.Ledger.Shelley.Genesis Methods toJSON :: NominalDiffTimeMicro -> Value # toEncoding :: NominalDiffTimeMicro -> Encoding # toJSONList :: [NominalDiffTimeMicro] -> Value # toEncodingList :: [NominalDiffTimeMicro] -> Encoding # omitField :: NominalDiffTimeMicro -> Bool # | |
ToJSON ShelleyGenesis | |
Defined in Cardano.Ledger.Shelley.Genesis Methods toJSON :: ShelleyGenesis -> Value # toEncoding :: ShelleyGenesis -> Encoding # toJSONList :: [ShelleyGenesis] -> Value # toEncodingList :: [ShelleyGenesis] -> Encoding # omitField :: ShelleyGenesis -> Bool # | |
ToJSON ShelleyGenesisStaking | |
Defined in Cardano.Ledger.Shelley.Genesis Methods toJSON :: ShelleyGenesisStaking -> Value # toEncoding :: ShelleyGenesisStaking -> Encoding # toJSONList :: [ShelleyGenesisStaking] -> Value # toEncodingList :: [ShelleyGenesisStaking] -> Encoding # omitField :: ShelleyGenesisStaking -> Bool # | |
ToJSON Likelihood | |
Defined in Cardano.Ledger.Shelley.PoolRank Methods toJSON :: Likelihood -> Value # toEncoding :: Likelihood -> Encoding # toJSONList :: [Likelihood] -> Value # toEncodingList :: [Likelihood] -> Encoding # omitField :: Likelihood -> Bool # | |
ToJSON LogWeight | |
ToJSON NonMyopic | |
ToJSON Desirability | |
Defined in Cardano.Ledger.Shelley.RewardProvenance Methods toJSON :: Desirability -> Value # toEncoding :: Desirability -> Encoding # toJSONList :: [Desirability] -> Value # toEncodingList :: [Desirability] -> Encoding # omitField :: Desirability -> Bool # | |
ToJSON RewardProvenance | |
Defined in Cardano.Ledger.Shelley.RewardProvenance Methods toJSON :: RewardProvenance -> Value # toEncoding :: RewardProvenance -> Encoding # toJSONList :: [RewardProvenance] -> Value # toEncodingList :: [RewardProvenance] -> Encoding # omitField :: RewardProvenance -> Bool # | |
ToJSON RewardProvenancePool | |
Defined in Cardano.Ledger.Shelley.RewardProvenance Methods toJSON :: RewardProvenancePool -> Value # toEncoding :: RewardProvenancePool -> Encoding # toJSONList :: [RewardProvenancePool] -> Value # toEncodingList :: [RewardProvenancePool] -> Encoding # omitField :: RewardProvenancePool -> Bool # | |
ToJSON PulsingRewUpdate | |
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods toJSON :: PulsingRewUpdate -> Value # toEncoding :: PulsingRewUpdate -> Encoding # toJSONList :: [PulsingRewUpdate] -> Value # toEncodingList :: [PulsingRewUpdate] -> Encoding # omitField :: PulsingRewUpdate -> Bool # | |
ToJSON RewardUpdate | |
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods toJSON :: RewardUpdate -> Value # toEncoding :: RewardUpdate -> Encoding # toJSONList :: [RewardUpdate] -> Value # toEncodingList :: [RewardUpdate] -> Encoding # omitField :: RewardUpdate -> Bool # | |
ToJSON GenesisDelegCert | |
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: GenesisDelegCert -> Value # toEncoding :: GenesisDelegCert -> Encoding # toJSONList :: [GenesisDelegCert] -> Value # toEncodingList :: [GenesisDelegCert] -> Encoding # omitField :: GenesisDelegCert -> Bool # | |
ToJSON MIRCert | |
ToJSON MIRPot | |
ToJSON MIRTarget | |
ToJSON ShelleyDelegCert | |
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: ShelleyDelegCert -> Value # toEncoding :: ShelleyDelegCert -> Encoding # toJSONList :: [ShelleyDelegCert] -> Value # toEncodingList :: [ShelleyDelegCert] -> Encoding # omitField :: ShelleyDelegCert -> Bool # | |
ToJSON ShutdownOn | |
Defined in Cardano.Node.Handlers.Shutdown Methods toJSON :: ShutdownOn -> Value # toEncoding :: ShutdownOn -> Encoding # toJSONList :: [ShutdownOn] -> Value # toEncodingList :: [ShutdownOn] -> Encoding # omitField :: ShutdownOn -> Bool # | |
ToJSON ShutdownTrace | |
Defined in Cardano.Node.Handlers.Shutdown Methods toJSON :: ShutdownTrace -> Value # toEncoding :: ShutdownTrace -> Encoding # toJSONList :: [ShutdownTrace] -> Value # toEncodingList :: [ShutdownTrace] -> Encoding # omitField :: ShutdownTrace -> Bool # | |
ToJSON NodeInfo | |
ToJSON NodeStartupInfo | |
Defined in Cardano.Node.Startup Methods toJSON :: NodeStartupInfo -> Value # toEncoding :: NodeStartupInfo -> Encoding # toJSONList :: [NodeStartupInfo] -> Value # toEncodingList :: [NodeStartupInfo] -> Encoding # omitField :: NodeStartupInfo -> Bool # | |
ToJSON CheckpointsHash | |
Defined in Cardano.Node.Types Methods toJSON :: CheckpointsHash -> Value # toEncoding :: CheckpointsHash -> Encoding # toJSONList :: [CheckpointsHash] -> Value # toEncodingList :: [CheckpointsHash] -> Encoding # omitField :: CheckpointsHash -> Bool # | |
ToJSON GenesisHash | |
Defined in Cardano.Node.Types Methods toJSON :: GenesisHash -> Value # toEncoding :: GenesisHash -> Encoding # toJSONList :: [GenesisHash] -> Value # toEncodingList :: [GenesisHash] -> Encoding # omitField :: GenesisHash -> Bool # | |
ToJSON NodeDiffusionMode | |
Defined in Cardano.Node.Types Methods toJSON :: NodeDiffusionMode -> Value # toEncoding :: NodeDiffusionMode -> Encoding # toJSONList :: [NodeDiffusionMode] -> Value # toEncodingList :: [NodeDiffusionMode] -> Encoding # omitField :: NodeDiffusionMode -> Bool # | |
ToJSON PeerSnapshotFile | |
Defined in Cardano.Node.Types Methods toJSON :: PeerSnapshotFile -> Value # toEncoding :: PeerSnapshotFile -> Encoding # toJSONList :: [PeerSnapshotFile] -> Value # toEncodingList :: [PeerSnapshotFile] -> Encoding # omitField :: PeerSnapshotFile -> Bool # | |
ToJSON InitiatorOnly | |
Defined in Cardano.Network.Ping Methods toJSON :: InitiatorOnly -> Value # toEncoding :: InitiatorOnly -> Encoding # toJSONList :: [InitiatorOnly] -> Value # toEncodingList :: [InitiatorOnly] -> Encoding # omitField :: InitiatorOnly -> Bool # | |
ToJSON NodeVersion | |
Defined in Cardano.Network.Ping Methods toJSON :: NodeVersion -> Value # toEncoding :: NodeVersion -> Encoding # toJSONList :: [NodeVersion] -> Value # toEncodingList :: [NodeVersion] -> Encoding # omitField :: NodeVersion -> Bool # | |
ToJSON PeerSharing | |
Defined in Cardano.Network.Ping Methods toJSON :: PeerSharing -> Value # toEncoding :: PeerSharing -> Encoding # toJSONList :: [PeerSharing] -> Value # toEncodingList :: [PeerSharing] -> Encoding # | |
ToJSON PingTip | |
Defined in Cardano.Network.Ping Methods toEncoding :: PingTip -> Encoding # toJSONList :: [PingTip] -> Value # toEncodingList :: [PingTip] -> Encoding # | |
ToJSON StatPoint | |
ToJSON BlockNo | |
ToJSON EpochInterval | |
Defined in Cardano.Slotting.Slot Methods toJSON :: EpochInterval -> Value # toEncoding :: EpochInterval -> Encoding # toJSONList :: [EpochInterval] -> Value # toEncodingList :: [EpochInterval] -> Encoding # omitField :: EpochInterval -> Bool # | |
ToJSON EpochNo | |
ToJSON EpochSize | |
ToJSON SlotNo | |
ToJSON RelativeTime | |
Defined in Cardano.Slotting.Time Methods toJSON :: RelativeTime -> Value # toEncoding :: RelativeTime -> Encoding # toJSONList :: [RelativeTime] -> Value # toEncodingList :: [RelativeTime] -> Encoding # omitField :: RelativeTime -> Bool # | |
ToJSON SystemStart | |
Defined in Cardano.Slotting.Time Methods toJSON :: SystemStart -> Value # toEncoding :: SystemStart -> Encoding # toJSONList :: [SystemStart] -> Value # toEncodingList :: [SystemStart] -> Encoding # omitField :: SystemStart -> Bool # | |
ToJSON IntSet | |
ToJSON Void | |
ToJSON All | Since: aeson-2.2.3.0 |
ToJSON Any | Since: aeson-2.2.3.0 |
ToJSON Version | |
ToJSON CTime | |
ToJSON Int16 | |
ToJSON Int32 | |
ToJSON Int64 | |
ToJSON Int8 | |
ToJSON Word16 | |
ToJSON Word32 | |
ToJSON Word64 | |
ToJSON Word8 | |
ToJSON Ordering | |
ToJSON Aggregated | |
Defined in Cardano.BM.Data.Aggregated Methods toJSON :: Aggregated -> Value # toEncoding :: Aggregated -> Encoding # toJSONList :: [Aggregated] -> Value # toEncodingList :: [Aggregated] -> Encoding # omitField :: Aggregated -> Bool # | |
ToJSON BaseStats | |
ToJSON EWMA | |
ToJSON Measurable | |
Defined in Cardano.BM.Data.Aggregated Methods toJSON :: Measurable -> Value # toEncoding :: Measurable -> Encoding # toJSONList :: [Measurable] -> Value # toEncodingList :: [Measurable] -> Encoding # omitField :: Measurable -> Bool # | |
ToJSON Stats | |
ToJSON AggregatedKind | |
Defined in Cardano.BM.Data.AggregatedKind Methods toJSON :: AggregatedKind -> Value # toEncoding :: AggregatedKind -> Encoding # toJSONList :: [AggregatedKind] -> Value # toEncodingList :: [AggregatedKind] -> Encoding # omitField :: AggregatedKind -> Bool # | |
ToJSON BackendKind | |
Defined in Cardano.BM.Data.BackendKind Methods toJSON :: BackendKind -> Value # toEncoding :: BackendKind -> Encoding # toJSONList :: [BackendKind] -> Value # toEncodingList :: [BackendKind] -> Encoding # omitField :: BackendKind -> Bool # | |
ToJSON Endpoint | |
ToJSON RemoteAddr | |
Defined in Cardano.BM.Data.Configuration Methods toJSON :: RemoteAddr -> Value # toEncoding :: RemoteAddr -> Encoding # toJSONList :: [RemoteAddr] -> Value # toEncodingList :: [RemoteAddr] -> Encoding # omitField :: RemoteAddr -> Bool # | |
ToJSON RemoteAddrNamed | |
Defined in Cardano.BM.Data.Configuration Methods toJSON :: RemoteAddrNamed -> Value # toEncoding :: RemoteAddrNamed -> Encoding # toJSONList :: [RemoteAddrNamed] -> Value # toEncodingList :: [RemoteAddrNamed] -> Encoding # omitField :: RemoteAddrNamed -> Bool # | |
ToJSON Representation | |
Defined in Cardano.BM.Data.Configuration Methods toJSON :: Representation -> Value # toEncoding :: Representation -> Encoding # toJSONList :: [Representation] -> Value # toEncodingList :: [Representation] -> Encoding # omitField :: Representation -> Bool # | |
ToJSON Counter | |
ToJSON CounterState | |
Defined in Cardano.BM.Data.Counter Methods toJSON :: CounterState -> Value # toEncoding :: CounterState -> Encoding # toJSONList :: [CounterState] -> Value # toEncodingList :: [CounterState] -> Encoding # omitField :: CounterState -> Bool # | |
ToJSON CounterType | |
Defined in Cardano.BM.Data.Counter Methods toJSON :: CounterType -> Value # toEncoding :: CounterType -> Encoding # toJSONList :: [CounterType] -> Value # toEncodingList :: [CounterType] -> Encoding # omitField :: CounterType -> Bool # | |
ToJSON CommandValue | |
Defined in Cardano.BM.Data.LogItem Methods toJSON :: CommandValue -> Value # toEncoding :: CommandValue -> Encoding # toJSONList :: [CommandValue] -> Value # toEncodingList :: [CommandValue] -> Encoding # omitField :: CommandValue -> Bool # | |
ToJSON LOMeta | |
ToJSON MonitorAction | |
Defined in Cardano.BM.Data.LogItem Methods toJSON :: MonitorAction -> Value # toEncoding :: MonitorAction -> Encoding # toJSONList :: [MonitorAction] -> Value # toEncodingList :: [MonitorAction] -> Encoding # omitField :: MonitorAction -> Bool # | |
ToJSON ObservableInstance | |
Defined in Cardano.BM.Data.Observable Methods toJSON :: ObservableInstance -> Value # toEncoding :: ObservableInstance -> Encoding # toJSONList :: [ObservableInstance] -> Value # toEncodingList :: [ObservableInstance] -> Encoding # omitField :: ObservableInstance -> Bool # | |
ToJSON ScribeDefinition | |
Defined in Cardano.BM.Data.Output Methods toJSON :: ScribeDefinition -> Value # toEncoding :: ScribeDefinition -> Encoding # toJSONList :: [ScribeDefinition] -> Value # toEncodingList :: [ScribeDefinition] -> Encoding # omitField :: ScribeDefinition -> Bool # | |
ToJSON ScribeFormat | |
Defined in Cardano.BM.Data.Output Methods toJSON :: ScribeFormat -> Value # toEncoding :: ScribeFormat -> Encoding # toJSONList :: [ScribeFormat] -> Value # toEncodingList :: [ScribeFormat] -> Encoding # omitField :: ScribeFormat -> Bool # | |
ToJSON ScribeKind | |
Defined in Cardano.BM.Data.Output Methods toJSON :: ScribeKind -> Value # toEncoding :: ScribeKind -> Encoding # toJSONList :: [ScribeKind] -> Value # toEncodingList :: [ScribeKind] -> Encoding # omitField :: ScribeKind -> Bool # | |
ToJSON ScribePrivacy | |
Defined in Cardano.BM.Data.Output Methods toJSON :: ScribePrivacy -> Value # toEncoding :: ScribePrivacy -> Encoding # toJSONList :: [ScribePrivacy] -> Value # toEncodingList :: [ScribePrivacy] -> Encoding # omitField :: ScribePrivacy -> Bool # | |
ToJSON RotationParameters | |
Defined in Cardano.BM.Data.Rotation Methods toJSON :: RotationParameters -> Value # toEncoding :: RotationParameters -> Encoding # toJSONList :: [RotationParameters] -> Value # toEncodingList :: [RotationParameters] -> Encoding # omitField :: RotationParameters -> Bool # | |
ToJSON Severity | |
ToJSON DropName | |
ToJSON NameSelector | |
Defined in Cardano.BM.Data.SubTrace Methods toJSON :: NameSelector -> Value # toEncoding :: NameSelector -> Encoding # toJSONList :: [NameSelector] -> Value # toEncodingList :: [NameSelector] -> Encoding # omitField :: NameSelector -> Bool # | |
ToJSON SubTrace | |
ToJSON UnhideNames | |
Defined in Cardano.BM.Data.SubTrace Methods toJSON :: UnhideNames -> Value # toEncoding :: UnhideNames -> Encoding # toJSONList :: [UnhideNames] -> Value # toEncodingList :: [UnhideNames] -> Encoding # omitField :: UnhideNames -> Bool # | |
ToJSON Environment | |
Defined in Katip.Core Methods toJSON :: Environment -> Value # toEncoding :: Environment -> Encoding # toJSONList :: [Environment] -> Value # toEncodingList :: [Environment] -> Encoding # omitField :: Environment -> Bool # | |
ToJSON LocJs | |
ToJSON Namespace | |
ToJSON ProcessIDJs | |
Defined in Katip.Core Methods toJSON :: ProcessIDJs -> Value # toEncoding :: ProcessIDJs -> Encoding # toJSONList :: [ProcessIDJs] -> Value # toEncodingList :: [ProcessIDJs] -> Encoding # omitField :: ProcessIDJs -> Bool # | |
ToJSON Severity | |
ToJSON SimpleLogPayload | A built-in convenience log payload that won't log anything on Construct using |
Defined in Katip.Core Methods toJSON :: SimpleLogPayload -> Value # toEncoding :: SimpleLogPayload -> Encoding # toJSONList :: [SimpleLogPayload] -> Value # toEncodingList :: [SimpleLogPayload] -> Encoding # omitField :: SimpleLogPayload -> Bool # | |
ToJSON ThreadIdText | |
Defined in Katip.Core Methods toJSON :: ThreadIdText -> Value # toEncoding :: ThreadIdText -> Encoding # toJSONList :: [ThreadIdText] -> Value # toEncodingList :: [ThreadIdText] -> Encoding # omitField :: ThreadIdText -> Bool # | |
ToJSON Verbosity | |
ToJSON LogContexts | |
Defined in Katip.Monadic Methods toJSON :: LogContexts -> Value # toEncoding :: LogContexts -> Encoding # toJSONList :: [LogContexts] -> Value # toEncodingList :: [LogContexts] -> Encoding # omitField :: LogContexts -> Bool # | |
ToJSON ApiError | |
ToJSON AbsoluteSlot | |
Defined in Maestro.Types.Common Methods toJSON :: AbsoluteSlot -> Value # toEncoding :: AbsoluteSlot -> Encoding # toJSONList :: [AbsoluteSlot] -> Value # toEncodingList :: [AbsoluteSlot] -> Encoding # omitField :: AbsoluteSlot -> Bool # | |
ToJSON BlockHash | |
ToJSON BlockHeight | |
Defined in Maestro.Types.Common Methods toJSON :: BlockHeight -> Value # toEncoding :: BlockHeight -> Encoding # toJSONList :: [BlockHeight] -> Value # toEncodingList :: [BlockHeight] -> Encoding # omitField :: BlockHeight -> Bool # | |
ToJSON DatumOption | |
Defined in Maestro.Types.Common Methods toJSON :: DatumOption -> Value # toEncoding :: DatumOption -> Encoding # toJSONList :: [DatumOption] -> Value # toEncodingList :: [DatumOption] -> Encoding # omitField :: DatumOption -> Bool # | |
ToJSON DatumOptionType | |
Defined in Maestro.Types.Common Methods toJSON :: DatumOptionType -> Value # toEncoding :: DatumOptionType -> Encoding # toJSONList :: [DatumOptionType] -> Value # toEncodingList :: [DatumOptionType] -> Encoding # omitField :: DatumOptionType -> Bool # | |
ToJSON EpochNo | |
ToJSON EpochSize | |
ToJSON Order | |
ToJSON PolicyId | |
ToJSON Script | |
ToJSON ScriptType | |
Defined in Maestro.Types.Common Methods toJSON :: ScriptType -> Value # toEncoding :: ScriptType -> Encoding # toJSONList :: [ScriptType] -> Value # toEncodingList :: [ScriptType] -> Encoding # omitField :: ScriptType -> Bool # | |
ToJSON SlotNo | |
ToJSON TokenName | |
ToJSON TxHash | |
ToJSON TxIndex | |
ToJSON AccountAction | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountAction -> Value # toEncoding :: AccountAction -> Encoding # toJSONList :: [AccountAction] -> Value # toEncodingList :: [AccountAction] -> Encoding # | |
ToJSON AccountHistory | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountHistory -> Value # toEncoding :: AccountHistory -> Encoding # toJSONList :: [AccountHistory] -> Value # toEncodingList :: [AccountHistory] -> Encoding # omitField :: AccountHistory -> Bool # | |
ToJSON AccountInfo | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountInfo -> Value # toEncoding :: AccountInfo -> Encoding # toJSONList :: [AccountInfo] -> Value # toEncodingList :: [AccountInfo] -> Encoding # omitField :: AccountInfo -> Bool # | |
ToJSON AccountReward | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountReward -> Value # toEncoding :: AccountReward -> Encoding # toJSONList :: [AccountReward] -> Value # toEncodingList :: [AccountReward] -> Encoding # omitField :: AccountReward -> Bool # | |
ToJSON AccountStakingRewardType | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountStakingRewardType -> Value # toEncoding :: AccountStakingRewardType -> Encoding # toJSONList :: [AccountStakingRewardType] -> Value # | |
ToJSON AccountUpdate | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: AccountUpdate -> Value # toEncoding :: AccountUpdate -> Encoding # toJSONList :: [AccountUpdate] -> Value # toEncodingList :: [AccountUpdate] -> Encoding # omitField :: AccountUpdate -> Bool # | |
ToJSON PaginatedAccountHistory | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: PaginatedAccountHistory -> Value # toEncoding :: PaginatedAccountHistory -> Encoding # toJSONList :: [PaginatedAccountHistory] -> Value # | |
ToJSON PaginatedAccountReward | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: PaginatedAccountReward -> Value # toEncoding :: PaginatedAccountReward -> Encoding # toJSONList :: [PaginatedAccountReward] -> Value # toEncodingList :: [PaginatedAccountReward] -> Encoding # omitField :: PaginatedAccountReward -> Bool # | |
ToJSON PaginatedAccountUpdate | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: PaginatedAccountUpdate -> Value # toEncoding :: PaginatedAccountUpdate -> Encoding # toJSONList :: [PaginatedAccountUpdate] -> Value # toEncodingList :: [PaginatedAccountUpdate] -> Encoding # omitField :: PaginatedAccountUpdate -> Bool # | |
ToJSON PaginatedAddress | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: PaginatedAddress -> Value # toEncoding :: PaginatedAddress -> Encoding # toJSONList :: [PaginatedAddress] -> Value # toEncodingList :: [PaginatedAddress] -> Encoding # omitField :: PaginatedAddress -> Bool # | |
ToJSON PaginatedAsset | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: PaginatedAsset -> Value # toEncoding :: PaginatedAsset -> Encoding # toJSONList :: [PaginatedAsset] -> Value # toEncodingList :: [PaginatedAsset] -> Encoding # omitField :: PaginatedAsset -> Bool # | |
ToJSON TimestampedAccountInfo | |
Defined in Maestro.Types.V1.Accounts Methods toJSON :: TimestampedAccountInfo -> Value # toEncoding :: TimestampedAccountInfo -> Encoding # toJSONList :: [TimestampedAccountInfo] -> Value # toEncodingList :: [TimestampedAccountInfo] -> Encoding # omitField :: TimestampedAccountInfo -> Bool # | |
ToJSON AddressInfo | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |
ToJSON AddressTransaction | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: AddressTransaction -> Value # toEncoding :: AddressTransaction -> Encoding # toJSONList :: [AddressTransaction] -> Value # toEncodingList :: [AddressTransaction] -> Encoding # omitField :: AddressTransaction -> Bool # | |
ToJSON CertIndex | |
ToJSON ChainPointer | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: ChainPointer -> Value # toEncoding :: ChainPointer -> Encoding # toJSONList :: [ChainPointer] -> Value # toEncodingList :: [ChainPointer] -> Encoding # omitField :: ChainPointer -> Bool # | |
ToJSON NetworkId | |
ToJSON OutputReferenceObject | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: OutputReferenceObject -> Value # toEncoding :: OutputReferenceObject -> Encoding # toJSONList :: [OutputReferenceObject] -> Value # toEncodingList :: [OutputReferenceObject] -> Encoding # omitField :: OutputReferenceObject -> Bool # | |
ToJSON PaginatedAddressTransaction | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: PaginatedAddressTransaction -> Value # toEncoding :: PaginatedAddressTransaction -> Encoding # toJSONList :: [PaginatedAddressTransaction] -> Value # toEncodingList :: [PaginatedAddressTransaction] -> Encoding # | |
ToJSON PaginatedOutputReferenceObject | |
Defined in Maestro.Types.V1.Addresses | |
ToJSON PaginatedPaymentCredentialTransaction | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: PaginatedPaymentCredentialTransaction -> Value # toEncoding :: PaginatedPaymentCredentialTransaction -> Encoding # toJSONList :: [PaginatedPaymentCredentialTransaction] -> Value # toEncodingList :: [PaginatedPaymentCredentialTransaction] -> Encoding # omitField :: PaginatedPaymentCredentialTransaction -> Bool # | |
ToJSON PaymentCredKind | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: PaymentCredKind -> Value # toEncoding :: PaymentCredKind -> Encoding # toJSONList :: [PaymentCredKind] -> Value # toEncodingList :: [PaymentCredKind] -> Encoding # omitField :: PaymentCredKind -> Bool # | |
ToJSON PaymentCredential | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: PaymentCredential -> Value # toEncoding :: PaymentCredential -> Encoding # toJSONList :: [PaymentCredential] -> Value # toEncodingList :: [PaymentCredential] -> Encoding # omitField :: PaymentCredential -> Bool # | |
ToJSON PaymentCredentialTransaction | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: PaymentCredentialTransaction -> Value # toEncoding :: PaymentCredentialTransaction -> Encoding # toJSONList :: [PaymentCredentialTransaction] -> Value # toEncodingList :: [PaymentCredentialTransaction] -> Encoding # | |
ToJSON StakingCredKind | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: StakingCredKind -> Value # toEncoding :: StakingCredKind -> Encoding # toJSONList :: [StakingCredKind] -> Value # toEncodingList :: [StakingCredKind] -> Encoding # omitField :: StakingCredKind -> Bool # | |
ToJSON StakingCredential | |
Defined in Maestro.Types.V1.Addresses Methods toJSON :: StakingCredential -> Value # toEncoding :: StakingCredential -> Encoding # toJSONList :: [StakingCredential] -> Value # toEncodingList :: [StakingCredential] -> Encoding # omitField :: StakingCredential -> Bool # | |
ToJSON AssetInfo | |
ToJSON AssetStandards | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: AssetStandards -> Value # toEncoding :: AssetStandards -> Encoding # toJSONList :: [AssetStandards] -> Value # toEncodingList :: [AssetStandards] -> Encoding # | |
ToJSON AssetUTxOs | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: AssetUTxOs -> Value # toEncoding :: AssetUTxOs -> Encoding # toJSONList :: [AssetUTxOs] -> Value # toEncodingList :: [AssetUTxOs] -> Encoding # omitField :: AssetUTxOs -> Bool # | |
ToJSON Cip68AssetType | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: Cip68AssetType -> Value # toEncoding :: Cip68AssetType -> Encoding # toJSONList :: [Cip68AssetType] -> Value # toEncodingList :: [Cip68AssetType] -> Encoding # | |
ToJSON Cip68Metadata | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: Cip68Metadata -> Value # toEncoding :: Cip68Metadata -> Encoding # toJSONList :: [Cip68Metadata] -> Value # toEncodingList :: [Cip68Metadata] -> Encoding # | |
ToJSON TimestampedAssetInfo | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: TimestampedAssetInfo -> Value # toEncoding :: TimestampedAssetInfo -> Encoding # toJSONList :: [TimestampedAssetInfo] -> Value # toEncodingList :: [TimestampedAssetInfo] -> Encoding # omitField :: TimestampedAssetInfo -> Bool # | |
ToJSON TimestampedAssetUTxOs | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: TimestampedAssetUTxOs -> Value # toEncoding :: TimestampedAssetUTxOs -> Encoding # toJSONList :: [TimestampedAssetUTxOs] -> Value # toEncodingList :: [TimestampedAssetUTxOs] -> Encoding # omitField :: TimestampedAssetUTxOs -> Bool # | |
ToJSON TokenRegistryMetadata | |
Defined in Maestro.Types.V1.Assets Methods toJSON :: TokenRegistryMetadata -> Value # toEncoding :: TokenRegistryMetadata -> Encoding # toJSONList :: [TokenRegistryMetadata] -> Value # toEncodingList :: [TokenRegistryMetadata] -> Encoding # omitField :: TokenRegistryMetadata -> Bool # | |
ToJSON BlockDetails | |
Defined in Maestro.Types.V1.Blocks Methods toJSON :: BlockDetails -> Value # toEncoding :: BlockDetails -> Encoding # toJSONList :: [BlockDetails] -> Value # toEncodingList :: [BlockDetails] -> Encoding # omitField :: BlockDetails -> Bool # | |
ToJSON TimestampedBlockDetails | |
Defined in Maestro.Types.V1.Blocks Methods toJSON :: TimestampedBlockDetails -> Value # toEncoding :: TimestampedBlockDetails -> Encoding # toJSONList :: [TimestampedBlockDetails] -> Value # | |
ToJSON Asset | |
ToJSON AssetUnit | |
ToJSON PaginatedUtxoWithSlot | |
Defined in Maestro.Types.V1.Common Methods toJSON :: PaginatedUtxoWithSlot -> Value # toEncoding :: PaginatedUtxoWithSlot -> Encoding # toJSONList :: [PaginatedUtxoWithSlot] -> Value # toEncodingList :: [PaginatedUtxoWithSlot] -> Encoding # omitField :: PaginatedUtxoWithSlot -> Bool # | |
ToJSON UtxoWithSlot | |
Defined in Maestro.Types.V1.Common Methods toJSON :: UtxoWithSlot -> Value # toEncoding :: UtxoWithSlot -> Encoding # toJSONList :: [UtxoWithSlot] -> Value # toEncodingList :: [UtxoWithSlot] -> Encoding # omitField :: UtxoWithSlot -> Bool # | |
ToJSON NextCursor | |
Defined in Maestro.Types.V1.Common.Pagination Methods toJSON :: NextCursor -> Value # toEncoding :: NextCursor -> Encoding # toJSONList :: [NextCursor] -> Value # toEncodingList :: [NextCursor] -> Encoding # omitField :: NextCursor -> Bool # | |
ToJSON LastUpdated | |
Defined in Maestro.Types.V1.Common.Timestamped Methods toJSON :: LastUpdated -> Value # toEncoding :: LastUpdated -> Encoding # toJSONList :: [LastUpdated] -> Value # toEncodingList :: [LastUpdated] -> Encoding # omitField :: LastUpdated -> Bool # | |
ToJSON Datum | |
ToJSON TimestampedDatum | |
Defined in Maestro.Types.V1.Datum Methods toJSON :: TimestampedDatum -> Value # toEncoding :: TimestampedDatum -> Encoding # toJSONList :: [TimestampedDatum] -> Value # toEncodingList :: [TimestampedDatum] -> Encoding # omitField :: TimestampedDatum -> Bool # | |
ToJSON Dex | |
ToJSON Resolution | |
Defined in Maestro.Types.V1.DefiMarkets Methods toJSON :: Resolution -> Value # toEncoding :: Resolution -> Encoding # toJSONList :: [Resolution] -> Value # toEncodingList :: [Resolution] -> Encoding # omitField :: Resolution -> Bool # | |
ToJSON AsAda | |
ToJSON AsBytes | |
ToJSON AsLovelace | |
Defined in Maestro.Types.V1.General Methods toJSON :: AsLovelace -> Value # toEncoding :: AsLovelace -> Encoding # toJSONList :: [AsLovelace] -> Value # toEncodingList :: [AsLovelace] -> Encoding # omitField :: AsLovelace -> Bool # | |
ToJSON ChainTip | |
ToJSON ConstitutionalCommittee | |
Defined in Maestro.Types.V1.General Methods toJSON :: ConstitutionalCommittee -> Value # toEncoding :: ConstitutionalCommittee -> Encoding # toJSONList :: [ConstitutionalCommittee] -> Value # | |
ToJSON CostModel | |
ToJSON CostModels | |
Defined in Maestro.Types.V1.General Methods toJSON :: CostModels -> Value # toEncoding :: CostModels -> Encoding # toJSONList :: [CostModels] -> Value # toEncodingList :: [CostModels] -> Encoding # omitField :: CostModels -> Bool # | |
ToJSON DRepVotingThresholds | |
Defined in Maestro.Types.V1.General Methods toJSON :: DRepVotingThresholds -> Value # toEncoding :: DRepVotingThresholds -> Encoding # toJSONList :: [DRepVotingThresholds] -> Value # toEncodingList :: [DRepVotingThresholds] -> Encoding # omitField :: DRepVotingThresholds -> Bool # | |
ToJSON EpochSlotLength | |
Defined in Maestro.Types.V1.General Methods toJSON :: EpochSlotLength -> Value # toEncoding :: EpochSlotLength -> Encoding # toJSONList :: [EpochSlotLength] -> Value # toEncodingList :: [EpochSlotLength] -> Encoding # omitField :: EpochSlotLength -> Bool # | |
ToJSON EraBound | |
ToJSON EraBoundTime | |
Defined in Maestro.Types.V1.General Methods toJSON :: EraBoundTime -> Value # toEncoding :: EraBoundTime -> Encoding # toJSONList :: [EraBoundTime] -> Value # toEncodingList :: [EraBoundTime] -> Encoding # omitField :: EraBoundTime -> Bool # | |
ToJSON EraParameters | |
Defined in Maestro.Types.V1.General Methods toJSON :: EraParameters -> Value # toEncoding :: EraParameters -> Encoding # toJSONList :: [EraParameters] -> Value # toEncodingList :: [EraParameters] -> Encoding # omitField :: EraParameters -> Bool # | |
ToJSON EraSummary | |
Defined in Maestro.Types.V1.General Methods toJSON :: EraSummary -> Value # toEncoding :: EraSummary -> Encoding # toJSONList :: [EraSummary] -> Value # toEncodingList :: [EraSummary] -> Encoding # omitField :: EraSummary -> Bool # | |
ToJSON MaestroRational | |
Defined in Maestro.Types.V1.General Methods toJSON :: MaestroRational -> Value # toEncoding :: MaestroRational -> Encoding # toJSONList :: [MaestroRational] -> Value # toEncodingList :: [MaestroRational] -> Encoding # omitField :: MaestroRational -> Bool # | |
ToJSON MinFeeReferenceScripts | |
Defined in Maestro.Types.V1.General Methods toJSON :: MinFeeReferenceScripts -> Value # toEncoding :: MinFeeReferenceScripts -> Encoding # toJSONList :: [MinFeeReferenceScripts] -> Value # toEncodingList :: [MinFeeReferenceScripts] -> Encoding # omitField :: MinFeeReferenceScripts -> Bool # | |
ToJSON ProtocolParameters | |
Defined in Maestro.Types.V1.General Methods toJSON :: ProtocolParameters -> Value # toEncoding :: ProtocolParameters -> Encoding # toJSONList :: [ProtocolParameters] -> Value # toEncodingList :: [ProtocolParameters] -> Encoding # omitField :: ProtocolParameters -> Bool # | |
ToJSON ProtocolParametersUpdateDRep | |
Defined in Maestro.Types.V1.General Methods toJSON :: ProtocolParametersUpdateDRep -> Value # toEncoding :: ProtocolParametersUpdateDRep -> Encoding # toJSONList :: [ProtocolParametersUpdateDRep] -> Value # toEncodingList :: [ProtocolParametersUpdateDRep] -> Encoding # | |
ToJSON ProtocolParametersUpdateStakePool | |
Defined in Maestro.Types.V1.General | |
ToJSON ProtocolVersion | |
Defined in Maestro.Types.V1.General Methods toJSON :: ProtocolVersion -> Value # toEncoding :: ProtocolVersion -> Encoding # toJSONList :: [ProtocolVersion] -> Value # toEncodingList :: [ProtocolVersion] -> Encoding # omitField :: ProtocolVersion -> Bool # | |
ToJSON StakePoolVotingThresholds | |
Defined in Maestro.Types.V1.General Methods toJSON :: StakePoolVotingThresholds -> Value # toEncoding :: StakePoolVotingThresholds -> Encoding # toJSONList :: [StakePoolVotingThresholds] -> Value # | |
ToJSON TimestampedChainTip | |
Defined in Maestro.Types.V1.General Methods toJSON :: TimestampedChainTip -> Value # toEncoding :: TimestampedChainTip -> Encoding # toJSONList :: [TimestampedChainTip] -> Value # toEncodingList :: [TimestampedChainTip] -> Encoding # omitField :: TimestampedChainTip -> Bool # | |
ToJSON TimestampedEraSummaries | |
Defined in Maestro.Types.V1.General Methods toJSON :: TimestampedEraSummaries -> Value # toEncoding :: TimestampedEraSummaries -> Encoding # toJSONList :: [TimestampedEraSummaries] -> Value # | |
ToJSON TimestampedProtocolParameters | |
Defined in Maestro.Types.V1.General | |
ToJSON TimestampedSystemStart | |
Defined in Maestro.Types.V1.General Methods toJSON :: TimestampedSystemStart -> Value # toEncoding :: TimestampedSystemStart -> Encoding # toJSONList :: [TimestampedSystemStart] -> Value # toEncodingList :: [TimestampedSystemStart] -> Encoding # omitField :: TimestampedSystemStart -> Bool # | |
ToJSON PaginatedPoolListInfo | |
Defined in Maestro.Types.V1.Pools Methods toJSON :: PaginatedPoolListInfo -> Value # toEncoding :: PaginatedPoolListInfo -> Encoding # toJSONList :: [PaginatedPoolListInfo] -> Value # toEncodingList :: [PaginatedPoolListInfo] -> Encoding # omitField :: PaginatedPoolListInfo -> Bool # | |
ToJSON PoolListInfo | |
Defined in Maestro.Types.V1.Pools Methods toJSON :: PoolListInfo -> Value # toEncoding :: PoolListInfo -> Encoding # toJSONList :: [PoolListInfo] -> Value # toEncodingList :: [PoolListInfo] -> Encoding # omitField :: PoolListInfo -> Bool # | |
ToJSON OutputReference | |
Defined in Maestro.Types.V1.Transactions Methods toJSON :: OutputReference -> Value # toEncoding :: OutputReference -> Encoding # toJSONList :: [OutputReference] -> Value # toEncodingList :: [OutputReference] -> Encoding # omitField :: OutputReference -> Bool # | |
ToJSON PaginatedUtxo | |
Defined in Maestro.Types.V1.Transactions Methods toJSON :: PaginatedUtxo -> Value # toEncoding :: PaginatedUtxo -> Encoding # toJSONList :: [PaginatedUtxo] -> Value # toEncodingList :: [PaginatedUtxo] -> Encoding # omitField :: PaginatedUtxo -> Bool # | |
ToJSON TimestampedTxDetails | |
Defined in Maestro.Types.V1.Transactions Methods toJSON :: TimestampedTxDetails -> Value # toEncoding :: TimestampedTxDetails -> Encoding # toJSONList :: [TimestampedTxDetails] -> Value # toEncodingList :: [TimestampedTxDetails] -> Encoding # omitField :: TimestampedTxDetails -> Bool # | |
ToJSON TxDetails | |
ToJSON UtxoWithBytes | |
Defined in Maestro.Types.V1.Transactions Methods toJSON :: UtxoWithBytes -> Value # toEncoding :: UtxoWithBytes -> Encoding # toJSONList :: [UtxoWithBytes] -> Value # toEncodingList :: [UtxoWithBytes] -> Encoding # omitField :: UtxoWithBytes -> Bool # | |
ToJSON URI | Since: aeson-2.2.0.0 |
ToJSON AdditionalProperties | |
Defined in Data.OpenApi.Internal Methods toJSON :: AdditionalProperties -> Value # toEncoding :: AdditionalProperties -> Encoding # toJSONList :: [AdditionalProperties] -> Value # toEncodingList :: [AdditionalProperties] -> Encoding # omitField :: AdditionalProperties -> Bool # | |
ToJSON ApiKeyLocation | |
Defined in Data.OpenApi.Internal Methods toJSON :: ApiKeyLocation -> Value # toEncoding :: ApiKeyLocation -> Encoding # toJSONList :: [ApiKeyLocation] -> Value # toEncodingList :: [ApiKeyLocation] -> Encoding # omitField :: ApiKeyLocation -> Bool # | |
ToJSON ApiKeyParams | |
Defined in Data.OpenApi.Internal Methods toJSON :: ApiKeyParams -> Value # toEncoding :: ApiKeyParams -> Encoding # toJSONList :: [ApiKeyParams] -> Value # toEncodingList :: [ApiKeyParams] -> Encoding # omitField :: ApiKeyParams -> Bool # | |
ToJSON Callback | |
ToJSON Components | |
Defined in Data.OpenApi.Internal Methods toJSON :: Components -> Value # toEncoding :: Components -> Encoding # toJSONList :: [Components] -> Value # toEncodingList :: [Components] -> Encoding # omitField :: Components -> Bool # | |
ToJSON Contact | |
ToJSON Discriminator | |
Defined in Data.OpenApi.Internal Methods toJSON :: Discriminator -> Value # toEncoding :: Discriminator -> Encoding # toJSONList :: [Discriminator] -> Value # toEncodingList :: [Discriminator] -> Encoding # omitField :: Discriminator -> Bool # | |
ToJSON Encoding | |
ToJSON Example | |
ToJSON ExpressionOrValue | |
Defined in Data.OpenApi.Internal Methods toJSON :: ExpressionOrValue -> Value # toEncoding :: ExpressionOrValue -> Encoding # toJSONList :: [ExpressionOrValue] -> Value # toEncodingList :: [ExpressionOrValue] -> Encoding # omitField :: ExpressionOrValue -> Bool # | |
ToJSON ExternalDocs | |
Defined in Data.OpenApi.Internal Methods toJSON :: ExternalDocs -> Value # toEncoding :: ExternalDocs -> Encoding # toJSONList :: [ExternalDocs] -> Value # toEncodingList :: [ExternalDocs] -> Encoding # omitField :: ExternalDocs -> Bool # | |
ToJSON Header | |
ToJSON Info | |
ToJSON License | |
ToJSON Link | |
ToJSON MediaTypeObject | |
Defined in Data.OpenApi.Internal Methods toJSON :: MediaTypeObject -> Value # toEncoding :: MediaTypeObject -> Encoding # toJSONList :: [MediaTypeObject] -> Value # toEncodingList :: [MediaTypeObject] -> Encoding # omitField :: MediaTypeObject -> Bool # | |
ToJSON MimeList | |
ToJSON OAuth2AuthorizationCodeFlow | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2AuthorizationCodeFlow -> Value # toEncoding :: OAuth2AuthorizationCodeFlow -> Encoding # toJSONList :: [OAuth2AuthorizationCodeFlow] -> Value # toEncodingList :: [OAuth2AuthorizationCodeFlow] -> Encoding # | |
ToJSON OAuth2ClientCredentialsFlow | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2ClientCredentialsFlow -> Value # toEncoding :: OAuth2ClientCredentialsFlow -> Encoding # toJSONList :: [OAuth2ClientCredentialsFlow] -> Value # toEncodingList :: [OAuth2ClientCredentialsFlow] -> Encoding # | |
ToJSON OAuth2Flows | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2Flows -> Value # toEncoding :: OAuth2Flows -> Encoding # toJSONList :: [OAuth2Flows] -> Value # toEncodingList :: [OAuth2Flows] -> Encoding # omitField :: OAuth2Flows -> Bool # | |
ToJSON OAuth2ImplicitFlow | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2ImplicitFlow -> Value # toEncoding :: OAuth2ImplicitFlow -> Encoding # toJSONList :: [OAuth2ImplicitFlow] -> Value # toEncodingList :: [OAuth2ImplicitFlow] -> Encoding # omitField :: OAuth2ImplicitFlow -> Bool # | |
ToJSON OAuth2PasswordFlow | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2PasswordFlow -> Value # toEncoding :: OAuth2PasswordFlow -> Encoding # toJSONList :: [OAuth2PasswordFlow] -> Value # toEncodingList :: [OAuth2PasswordFlow] -> Encoding # omitField :: OAuth2PasswordFlow -> Bool # | |
ToJSON OpenApi | |
ToJSON OpenApiItems | As for nullary schema for 0-arity type constructors, see https://github.com/GetShopTV/swagger2/issues/167.
|
Defined in Data.OpenApi.Internal Methods toJSON :: OpenApiItems -> Value # toEncoding :: OpenApiItems -> Encoding # toJSONList :: [OpenApiItems] -> Value # toEncodingList :: [OpenApiItems] -> Encoding # omitField :: OpenApiItems -> Bool # | |
ToJSON OpenApiSpecVersion | |
Defined in Data.OpenApi.Internal Methods toJSON :: OpenApiSpecVersion -> Value # toEncoding :: OpenApiSpecVersion -> Encoding # toJSONList :: [OpenApiSpecVersion] -> Value # toEncodingList :: [OpenApiSpecVersion] -> Encoding # omitField :: OpenApiSpecVersion -> Bool # | |
ToJSON OpenApiType | |
Defined in Data.OpenApi.Internal Methods toJSON :: OpenApiType -> Value # toEncoding :: OpenApiType -> Encoding # toJSONList :: [OpenApiType] -> Value # toEncodingList :: [OpenApiType] -> Encoding # omitField :: OpenApiType -> Bool # | |
ToJSON Operation | |
ToJSON Param | |
ToJSON ParamLocation | |
Defined in Data.OpenApi.Internal Methods toJSON :: ParamLocation -> Value # toEncoding :: ParamLocation -> Encoding # toJSONList :: [ParamLocation] -> Value # toEncodingList :: [ParamLocation] -> Encoding # omitField :: ParamLocation -> Bool # | |
ToJSON PathItem | |
ToJSON Reference | |
ToJSON RequestBody | |
Defined in Data.OpenApi.Internal Methods toJSON :: RequestBody -> Value # toEncoding :: RequestBody -> Encoding # toJSONList :: [RequestBody] -> Value # toEncodingList :: [RequestBody] -> Encoding # omitField :: RequestBody -> Bool # | |
ToJSON Response | |
ToJSON Responses | |
ToJSON Schema | |
ToJSON SecurityDefinitions | |
Defined in Data.OpenApi.Internal Methods toJSON :: SecurityDefinitions -> Value # toEncoding :: SecurityDefinitions -> Encoding # toJSONList :: [SecurityDefinitions] -> Value # toEncodingList :: [SecurityDefinitions] -> Encoding # omitField :: SecurityDefinitions -> Bool # | |
ToJSON SecurityRequirement | |
Defined in Data.OpenApi.Internal Methods toJSON :: SecurityRequirement -> Value # toEncoding :: SecurityRequirement -> Encoding # toJSONList :: [SecurityRequirement] -> Value # toEncodingList :: [SecurityRequirement] -> Encoding # omitField :: SecurityRequirement -> Bool # | |
ToJSON SecurityScheme | |
Defined in Data.OpenApi.Internal Methods toJSON :: SecurityScheme -> Value # toEncoding :: SecurityScheme -> Encoding # toJSONList :: [SecurityScheme] -> Value # toEncodingList :: [SecurityScheme] -> Encoding # omitField :: SecurityScheme -> Bool # | |
ToJSON SecuritySchemeType | |
Defined in Data.OpenApi.Internal Methods toJSON :: SecuritySchemeType -> Value # toEncoding :: SecuritySchemeType -> Encoding # toJSONList :: [SecuritySchemeType] -> Value # toEncodingList :: [SecuritySchemeType] -> Encoding # omitField :: SecuritySchemeType -> Bool # | |
ToJSON Server | |
ToJSON ServerVariable | |
Defined in Data.OpenApi.Internal Methods toJSON :: ServerVariable -> Value # toEncoding :: ServerVariable -> Encoding # toJSONList :: [ServerVariable] -> Value # toEncodingList :: [ServerVariable] -> Encoding # omitField :: ServerVariable -> Bool # | |
ToJSON Style | |
ToJSON Tag | |
ToJSON URL | |
ToJSON Xml | |
ToJSON AccPoolStakeCoded | |
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Methods toJSON :: AccPoolStakeCoded -> Value # toEncoding :: AccPoolStakeCoded -> Encoding # toJSONList :: [AccPoolStakeCoded] -> Value # toEncodingList :: [AccPoolStakeCoded] -> Encoding # | |
ToJSON LedgerPeerSnapshot | |
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Methods toJSON :: LedgerPeerSnapshot -> Value # toEncoding :: LedgerPeerSnapshot -> Encoding # toJSONList :: [LedgerPeerSnapshot] -> Value # toEncodingList :: [LedgerPeerSnapshot] -> Encoding # omitField :: LedgerPeerSnapshot -> Bool # | |
ToJSON PoolStakeCoded | |
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Methods toJSON :: PoolStakeCoded -> Value # toEncoding :: PoolStakeCoded -> Encoding # toJSONList :: [PoolStakeCoded] -> Value # toEncodingList :: [PoolStakeCoded] -> Encoding # | |
ToJSON PeerAdvertise | |
Defined in Ouroboros.Network.PeerSelection.PeerAdvertise Methods toJSON :: PeerAdvertise -> Value # toEncoding :: PeerAdvertise -> Encoding # toJSONList :: [PeerAdvertise] -> Value # toEncodingList :: [PeerAdvertise] -> Encoding # omitField :: PeerAdvertise -> Bool # | |
ToJSON DomainAccessPoint | |
Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint Methods toJSON :: DomainAccessPoint -> Value # toEncoding :: DomainAccessPoint -> Encoding # toJSONList :: [DomainAccessPoint] -> Value # toEncodingList :: [DomainAccessPoint] -> Encoding # omitField :: DomainAccessPoint -> Bool # | |
ToJSON RelayAccessPoint | |
Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint Methods toJSON :: RelayAccessPoint -> Value # toEncoding :: RelayAccessPoint -> Encoding # toJSONList :: [RelayAccessPoint] -> Value # toEncodingList :: [RelayAccessPoint] -> Encoding # omitField :: RelayAccessPoint -> Bool # | |
ToJSON ExBudget | |
ToJSON ExCPU | |
ToJSON ExMemory | |
ToJSON SatInt | |
ToJSON ContractBlueprint | |
Defined in PlutusTx.Blueprint.Contract Methods toJSON :: ContractBlueprint -> Value # toEncoding :: ContractBlueprint -> Encoding # toJSONList :: [ContractBlueprint] -> Value # toEncodingList :: [ContractBlueprint] -> Encoding # omitField :: ContractBlueprint -> Bool # | |
ToJSON DefinitionId | |
Defined in PlutusTx.Blueprint.Definition.Id Methods toJSON :: DefinitionId -> Value # toEncoding :: DefinitionId -> Encoding # toJSONList :: [DefinitionId] -> Value # toEncodingList :: [DefinitionId] -> Encoding # omitField :: DefinitionId -> Bool # | |
ToJSON PlutusVersion | |
Defined in PlutusTx.Blueprint.PlutusVersion Methods toJSON :: PlutusVersion -> Value # toEncoding :: PlutusVersion -> Encoding # toJSONList :: [PlutusVersion] -> Value # toEncodingList :: [PlutusVersion] -> Encoding # omitField :: PlutusVersion -> Bool # | |
ToJSON Preamble | |
ToJSON Purpose | |
ToJSON SchemaComment | |
Defined in PlutusTx.Blueprint.Schema.Annotation Methods toJSON :: SchemaComment -> Value # toEncoding :: SchemaComment -> Encoding # toJSONList :: [SchemaComment] -> Value # toEncodingList :: [SchemaComment] -> Encoding # omitField :: SchemaComment -> Bool # | |
ToJSON SchemaDescription | |
Defined in PlutusTx.Blueprint.Schema.Annotation Methods toJSON :: SchemaDescription -> Value # toEncoding :: SchemaDescription -> Encoding # toJSONList :: [SchemaDescription] -> Value # toEncodingList :: [SchemaDescription] -> Encoding # omitField :: SchemaDescription -> Bool # | |
ToJSON SchemaTitle | |
Defined in PlutusTx.Blueprint.Schema.Annotation Methods toJSON :: SchemaTitle -> Value # toEncoding :: SchemaTitle -> Encoding # toJSONList :: [SchemaTitle] -> Value # toEncodingList :: [SchemaTitle] -> Encoding # omitField :: SchemaTitle -> Bool # | |
ToJSON CovLoc | |
ToJSON CoverageAnnotation | |
Defined in PlutusTx.Coverage Methods toJSON :: CoverageAnnotation -> Value # toEncoding :: CoverageAnnotation -> Encoding # toJSONList :: [CoverageAnnotation] -> Value # toEncodingList :: [CoverageAnnotation] -> Encoding # omitField :: CoverageAnnotation -> Bool # | |
ToJSON CoverageData | |
Defined in PlutusTx.Coverage Methods toJSON :: CoverageData -> Value # toEncoding :: CoverageData -> Encoding # toJSONList :: [CoverageData] -> Value # toEncodingList :: [CoverageData] -> Encoding # omitField :: CoverageData -> Bool # | |
ToJSON CoverageIndex | |
Defined in PlutusTx.Coverage Methods toJSON :: CoverageIndex -> Value # toEncoding :: CoverageIndex -> Encoding # toJSONList :: [CoverageIndex] -> Value # toEncodingList :: [CoverageIndex] -> Encoding # omitField :: CoverageIndex -> Bool # | |
ToJSON CoverageMetadata | |
Defined in PlutusTx.Coverage Methods toJSON :: CoverageMetadata -> Value # toEncoding :: CoverageMetadata -> Encoding # toJSONList :: [CoverageMetadata] -> Value # toEncodingList :: [CoverageMetadata] -> Encoding # omitField :: CoverageMetadata -> Bool # | |
ToJSON CoverageReport | |
Defined in PlutusTx.Coverage Methods toJSON :: CoverageReport -> Value # toEncoding :: CoverageReport -> Encoding # toJSONList :: [CoverageReport] -> Value # toEncodingList :: [CoverageReport] -> Encoding # omitField :: CoverageReport -> Bool # | |
ToJSON Metadata | |
ToJSON Rational | This mimics the behaviour of Aeson's instance for |
ToJSON SentryLevel | |
Defined in System.Log.Raven.Types Methods toJSON :: SentryLevel -> Value # toEncoding :: SentryLevel -> Encoding # toJSONList :: [SentryLevel] -> Value # toEncodingList :: [SentryLevel] -> Encoding # omitField :: SentryLevel -> Bool # | |
ToJSON SentryRecord | |
Defined in System.Log.Raven.Types Methods toJSON :: SentryRecord -> Value # toEncoding :: SentryRecord -> Encoding # toJSONList :: [SentryRecord] -> Value # toEncodingList :: [SentryRecord] -> Encoding # omitField :: SentryRecord -> Bool # | |
ToJSON Scientific | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Scientific -> Value # toEncoding :: Scientific -> Encoding # toJSONList :: [Scientific] -> Value # toEncodingList :: [Scientific] -> Encoding # omitField :: Scientific -> Bool # | |
ToJSON BaseUrl |
|
ToJSON StudentT | |
ToJSON AdditionalProperties | |
Defined in Data.Swagger.Internal Methods toJSON :: AdditionalProperties -> Value # toEncoding :: AdditionalProperties -> Encoding # toJSONList :: [AdditionalProperties] -> Value # toEncodingList :: [AdditionalProperties] -> Encoding # omitField :: AdditionalProperties -> Bool # | |
ToJSON ApiKeyLocation | |
Defined in Data.Swagger.Internal Methods toJSON :: ApiKeyLocation -> Value # toEncoding :: ApiKeyLocation -> Encoding # toJSONList :: [ApiKeyLocation] -> Value # toEncodingList :: [ApiKeyLocation] -> Encoding # omitField :: ApiKeyLocation -> Bool # | |
ToJSON ApiKeyParams | |
Defined in Data.Swagger.Internal Methods toJSON :: ApiKeyParams -> Value # toEncoding :: ApiKeyParams -> Encoding # toJSONList :: [ApiKeyParams] -> Value # toEncodingList :: [ApiKeyParams] -> Encoding # omitField :: ApiKeyParams -> Bool # | |
ToJSON Contact | |
ToJSON Example | |
ToJSON ExternalDocs | |
Defined in Data.Swagger.Internal Methods toJSON :: ExternalDocs -> Value # toEncoding :: ExternalDocs -> Encoding # toJSONList :: [ExternalDocs] -> Value # toEncodingList :: [ExternalDocs] -> Encoding # omitField :: ExternalDocs -> Bool # | |
ToJSON Header | |
ToJSON Host | |
ToJSON Info | |
ToJSON License | |
ToJSON MimeList | |
ToJSON OAuth2Flow | |
Defined in Data.Swagger.Internal Methods toJSON :: OAuth2Flow -> Value # toEncoding :: OAuth2Flow -> Encoding # toJSONList :: [OAuth2Flow] -> Value # toEncodingList :: [OAuth2Flow] -> Encoding # omitField :: OAuth2Flow -> Bool # | |
ToJSON OAuth2Params | |
Defined in Data.Swagger.Internal Methods toJSON :: OAuth2Params -> Value # toEncoding :: OAuth2Params -> Encoding # toJSONList :: [OAuth2Params] -> Value # toEncodingList :: [OAuth2Params] -> Encoding # omitField :: OAuth2Params -> Bool # | |
ToJSON Operation | |
ToJSON Param | |
ToJSON ParamAnySchema | |
Defined in Data.Swagger.Internal Methods toJSON :: ParamAnySchema -> Value # toEncoding :: ParamAnySchema -> Encoding # toJSONList :: [ParamAnySchema] -> Value # toEncodingList :: [ParamAnySchema] -> Encoding # omitField :: ParamAnySchema -> Bool # | |
ToJSON ParamLocation | |
Defined in Data.Swagger.Internal Methods toJSON :: ParamLocation -> Value # toEncoding :: ParamLocation -> Encoding # toJSONList :: [ParamLocation] -> Value # toEncodingList :: [ParamLocation] -> Encoding # omitField :: ParamLocation -> Bool # | |
ToJSON ParamOtherSchema | |
Defined in Data.Swagger.Internal Methods toJSON :: ParamOtherSchema -> Value # toEncoding :: ParamOtherSchema -> Encoding # toJSONList :: [ParamOtherSchema] -> Value # toEncodingList :: [ParamOtherSchema] -> Encoding # omitField :: ParamOtherSchema -> Bool # | |
ToJSON PathItem | |
ToJSON Reference | |
ToJSON Response | |
ToJSON Responses | |
ToJSON Schema | |
ToJSON Scheme | |
ToJSON SecurityDefinitions | |
Defined in Data.Swagger.Internal Methods toJSON :: SecurityDefinitions -> Value # toEncoding :: SecurityDefinitions -> Encoding # toJSONList :: [SecurityDefinitions] -> Value # toEncodingList :: [SecurityDefinitions] -> Encoding # omitField :: SecurityDefinitions -> Bool # | |
ToJSON SecurityRequirement | |
Defined in Data.Swagger.Internal Methods toJSON :: SecurityRequirement -> Value # toEncoding :: SecurityRequirement -> Encoding # toJSONList :: [SecurityRequirement] -> Value # toEncodingList :: [SecurityRequirement] -> Encoding # omitField :: SecurityRequirement -> Bool # | |
ToJSON SecurityScheme | |
Defined in Data.Swagger.Internal Methods toJSON :: SecurityScheme -> Value # toEncoding :: SecurityScheme -> Encoding # toJSONList :: [SecurityScheme] -> Value # toEncodingList :: [SecurityScheme] -> Encoding # omitField :: SecurityScheme -> Bool # | |
ToJSON SecuritySchemeType | |
Defined in Data.Swagger.Internal Methods toJSON :: SecuritySchemeType -> Value # toEncoding :: SecuritySchemeType -> Encoding # toJSONList :: [SecuritySchemeType] -> Value # toEncodingList :: [SecuritySchemeType] -> Encoding # omitField :: SecuritySchemeType -> Bool # | |
ToJSON Swagger | |
ToJSON Tag | |
ToJSON URL | |
ToJSON Xml | |
ToJSON Text | |
ToJSON Text | |
ToJSON ShortText | Since: aeson-2.0.2.0 |
ToJSON CalendarDiffDays | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: CalendarDiffDays -> Value # toEncoding :: CalendarDiffDays -> Encoding # toJSONList :: [CalendarDiffDays] -> Value # toEncodingList :: [CalendarDiffDays] -> Encoding # omitField :: CalendarDiffDays -> Bool # | |
ToJSON Day | |
ToJSON Month | |
ToJSON Quarter | |
ToJSON QuarterOfYear | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: QuarterOfYear -> Value # toEncoding :: QuarterOfYear -> Encoding # toJSONList :: [QuarterOfYear] -> Value # toEncodingList :: [QuarterOfYear] -> Encoding # omitField :: QuarterOfYear -> Bool # | |
ToJSON DayOfWeek | |
ToJSON DiffTime | |
ToJSON NominalDiffTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: NominalDiffTime -> Value # toEncoding :: NominalDiffTime -> Encoding # toJSONList :: [NominalDiffTime] -> Value # toEncodingList :: [NominalDiffTime] -> Encoding # omitField :: NominalDiffTime -> Bool # | |
ToJSON SystemTime | Encoded as number |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: SystemTime -> Value # toEncoding :: SystemTime -> Encoding # toJSONList :: [SystemTime] -> Value # toEncodingList :: [SystemTime] -> Encoding # omitField :: SystemTime -> Bool # | |
ToJSON UTCTime | |
ToJSON CalendarDiffTime | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: CalendarDiffTime -> Value # toEncoding :: CalendarDiffTime -> Encoding # toJSONList :: [CalendarDiffTime] -> Value # toEncodingList :: [CalendarDiffTime] -> Encoding # omitField :: CalendarDiffTime -> Bool # | |
ToJSON LocalTime | |
ToJSON TimeOfDay | |
ToJSON ZonedTime | |
ToJSON ConfigOptionRep | |
Defined in Cardano.Logging.ConfigurationParser Methods toJSON :: ConfigOptionRep -> Value # toEncoding :: ConfigOptionRep -> Encoding # toJSONList :: [ConfigOptionRep] -> Value # toEncodingList :: [ConfigOptionRep] -> Encoding # | |
ToJSON ConfigRepresentation | |
Defined in Cardano.Logging.ConfigurationParser Methods toJSON :: ConfigRepresentation -> Value # toEncoding :: ConfigRepresentation -> Encoding # toJSONList :: [ConfigRepresentation] -> Value # toEncodingList :: [ConfigRepresentation] -> Encoding # | |
ToJSON BackendConfig | |
Defined in Cardano.Logging.Types Methods toJSON :: BackendConfig -> Value # toEncoding :: BackendConfig -> Encoding # toJSONList :: [BackendConfig] -> Value # toEncodingList :: [BackendConfig] -> Encoding # omitField :: BackendConfig -> Bool # | |
ToJSON DetailLevel | |
Defined in Cardano.Logging.Types Methods toJSON :: DetailLevel -> Value # toEncoding :: DetailLevel -> Encoding # toJSONList :: [DetailLevel] -> Value # toEncodingList :: [DetailLevel] -> Encoding # omitField :: DetailLevel -> Bool # | |
ToJSON SeverityF | |
ToJSON SeverityS | |
ToJSON TraceOptionForwarder | |
Defined in Cardano.Logging.Types Methods toJSON :: TraceOptionForwarder -> Value # toEncoding :: TraceOptionForwarder -> Encoding # toJSONList :: [TraceOptionForwarder] -> Value # toEncodingList :: [TraceOptionForwarder] -> Encoding # omitField :: TraceOptionForwarder -> Bool # | |
ToJSON Verbosity | |
ToJSON UUID | |
ToJSON Integer | |
ToJSON Natural | |
ToJSON () | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: () -> Encoding # toJSONList :: [()] -> Value # toEncodingList :: [()] -> Encoding # | |
ToJSON Bool | |
ToJSON Char | |
ToJSON Double | |
ToJSON Float | |
ToJSON Int | |
ToJSON Word | |
ToJSON v => ToJSON (KeyMap v) | |
ToJSON a => ToJSON (Confidential a) # | |
Defined in GeniusYield.GYConfig Methods toJSON :: Confidential a -> Value # toEncoding :: Confidential a -> Encoding # toJSONList :: [Confidential a] -> Value # toEncodingList :: [Confidential a] -> Encoding # omitField :: Confidential a -> Bool # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYExtendedVerificationKeyToApi kr)) => ToJSON (GYExtendedVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods toJSON :: GYExtendedVerificationKey kr -> Value # toEncoding :: GYExtendedVerificationKey kr -> Encoding # toJSONList :: [GYExtendedVerificationKey kr] -> Value # toEncodingList :: [GYExtendedVerificationKey kr] -> Encoding # omitField :: GYExtendedVerificationKey kr -> Bool # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYSigningKeyToApi kr)) => ToJSON (GYSigningKey kr) # |
|
Defined in GeniusYield.Types.Key Methods toJSON :: GYSigningKey kr -> Value # toEncoding :: GYSigningKey kr -> Encoding # toJSONList :: [GYSigningKey kr] -> Value # toEncodingList :: [GYSigningKey kr] -> Encoding # omitField :: GYSigningKey kr -> Bool # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYVerificationKeyToApi kr)) => ToJSON (GYVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods toJSON :: GYVerificationKey kr -> Value # toEncoding :: GYVerificationKey kr -> Encoding # toJSONList :: [GYVerificationKey kr] -> Value # toEncodingList :: [GYVerificationKey kr] -> Encoding # omitField :: GYVerificationKey kr -> Bool # | |
ToJSON (GYKeyHash kr) # |
|
ToJSON a => ToJSON (First a) | |
ToJSON a => ToJSON (Last a) | |
ToJSON a => ToJSON (Max a) | |
ToJSON a => ToJSON (Min a) | |
ToJSON a => ToJSON (WrappedMonoid a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: WrappedMonoid a -> Value # toEncoding :: WrappedMonoid a -> Encoding # toJSONList :: [WrappedMonoid a] -> Value # toEncodingList :: [WrappedMonoid a] -> Encoding # omitField :: WrappedMonoid a -> Bool # | |
(Exception e, Generic e, GToJSON Zero (Rep e)) => ToJSON (WithErrorMessage e) | |
Defined in Cardano.Address.Internal Methods toJSON :: WithErrorMessage e -> Value # toEncoding :: WithErrorMessage e -> Encoding # toJSONList :: [WithErrorMessage e] -> Value # toEncodingList :: [WithErrorMessage e] -> Encoding # omitField :: WithErrorMessage e -> Bool # | |
ToJSON elem => ToJSON (Script elem) | |
ToJSON (Address ByronAddr) | |
ToJSON (Address ShelleyAddr) | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: Address ShelleyAddr -> Value # toEncoding :: Address ShelleyAddr -> Encoding # toJSONList :: [Address ShelleyAddr] -> Value # toEncodingList :: [Address ShelleyAddr] -> Encoding # omitField :: Address ShelleyAddr -> Bool # | |
IsCardanoEra era => ToJSON (AddressInEra era) | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: AddressInEra era -> Value # toEncoding :: AddressInEra era -> Encoding # toJSONList :: [AddressInEra era] -> Value # toEncodingList :: [AddressInEra era] -> Encoding # omitField :: AddressInEra era -> Bool # | |
ToJSON (ShelleyBasedEra era) | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toJSON :: ShelleyBasedEra era -> Value # toEncoding :: ShelleyBasedEra era -> Encoding # toJSONList :: [ShelleyBasedEra era] -> Value # toEncodingList :: [ShelleyBasedEra era] -> Encoding # omitField :: ShelleyBasedEra era -> Bool # | |
ToJSON (CardanoEra era) | |
Defined in Cardano.Api.Internal.Eras.Core Methods toJSON :: CardanoEra era -> Value # toEncoding :: CardanoEra era -> Encoding # toJSONList :: [CardanoEra era] -> Value # toEncodingList :: [CardanoEra era] -> Encoding # omitField :: CardanoEra era -> Bool # | |
ToJSON (Hash BlockHeader) | |
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value # toEncoding :: Hash BlockHeader -> Encoding # toJSONList :: [Hash BlockHeader] -> Value # toEncodingList :: [Hash BlockHeader] -> Encoding # omitField :: Hash BlockHeader -> Bool # | |
ToJSON (Hash DRepKey) | |
ToJSON (Hash GenesisKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash GenesisKey -> Value # toEncoding :: Hash GenesisKey -> Encoding # toJSONList :: [Hash GenesisKey] -> Value # toEncodingList :: [Hash GenesisKey] -> Encoding # omitField :: Hash GenesisKey -> Bool # | |
ToJSON (Hash PaymentKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash PaymentKey -> Value # toEncoding :: Hash PaymentKey -> Encoding # toJSONList :: [Hash PaymentKey] -> Value # toEncodingList :: [Hash PaymentKey] -> Encoding # omitField :: Hash PaymentKey -> Bool # | |
ToJSON (Hash StakePoolKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolKey -> Value # toEncoding :: Hash StakePoolKey -> Encoding # toJSONList :: [Hash StakePoolKey] -> Value # toEncodingList :: [Hash StakePoolKey] -> Encoding # omitField :: Hash StakePoolKey -> Bool # | |
ToJSON (Hash ScriptData) | |
Defined in Cardano.Api.Internal.ScriptData Methods toJSON :: Hash ScriptData -> Value # toEncoding :: Hash ScriptData -> Encoding # toJSONList :: [Hash ScriptData] -> Value # toEncodingList :: [Hash ScriptData] -> Encoding # omitField :: Hash ScriptData -> Bool # | |
ToJSON (TxValidationError era) | |
Defined in Cardano.Api.Internal.InMode Methods toJSON :: TxValidationError era -> Value # toEncoding :: TxValidationError era -> Encoding # toJSONList :: [TxValidationError era] -> Value # toEncodingList :: [TxValidationError era] -> Encoding # | |
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) | |
Defined in Cardano.Api.Internal.Query.Types Methods toJSON :: DebugLedgerState era -> Value # toEncoding :: DebugLedgerState era -> Encoding # toJSONList :: [DebugLedgerState era] -> Value # toEncodingList :: [DebugLedgerState era] -> Encoding # omitField :: DebugLedgerState era -> Bool # | |
IsCardanoEra era => ToJSON (ReferenceScript era) | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ReferenceScript era -> Value # toEncoding :: ReferenceScript era -> Encoding # toJSONList :: [ReferenceScript era] -> Value # toEncodingList :: [ReferenceScript era] -> Encoding # omitField :: ReferenceScript era -> Bool # | |
IsCardanoEra era => ToJSON (TxOutValue era) | |
Defined in Cardano.Api.Internal.Tx.Body Methods toJSON :: TxOutValue era -> Value # toEncoding :: TxOutValue era -> Encoding # toJSONList :: [TxOutValue era] -> Value # toEncodingList :: [TxOutValue era] -> Encoding # omitField :: TxOutValue era -> Bool # | |
IsCardanoEra era => ToJSON (UTxO era) | |
ToJSON a => ToJSON (RedeemSignature a) | |
Defined in Cardano.Crypto.Signing.Redeem.Signature Methods toJSON :: RedeemSignature a -> Value # toEncoding :: RedeemSignature a -> Encoding # toJSONList :: [RedeemSignature a] -> Value # toEncodingList :: [RedeemSignature a] -> Encoding # omitField :: RedeemSignature a -> Bool # | |
ToJSON (Signature w) | |
ToJSON a => ToJSON (OSet a) | |
(Era era, ToJSON (PlutusPurpose AsItem era), ToJSON (ContextError era)) => ToJSON (CollectError era) | |
Defined in Cardano.Ledger.Alonzo.Plutus.Evaluate Methods toJSON :: CollectError era -> Value # toEncoding :: CollectError era -> Encoding # toJSONList :: [CollectError era] -> Value # toEncodingList :: [CollectError era] -> Encoding # omitField :: CollectError era -> Bool # | |
AlonzoEraScript era => ToJSON (AlonzoScript era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods toJSON :: AlonzoScript era -> Value # toEncoding :: AlonzoScript era -> Encoding # toJSONList :: [AlonzoScript era] -> Value # toEncodingList :: [AlonzoScript era] -> Encoding # omitField :: AlonzoScript era -> Bool # | |
(Era era, Val (Value era)) => ToJSON (AlonzoTxOut era) | |
Defined in Cardano.Ledger.Alonzo.TxOut Methods toJSON :: AlonzoTxOut era -> Value # toEncoding :: AlonzoTxOut era -> Encoding # toJSONList :: [AlonzoTxOut era] -> Value # toEncodingList :: [AlonzoTxOut era] -> Encoding # omitField :: AlonzoTxOut era -> Bool # | |
ToJSON (PlutusPurpose AsIx era) => ToJSON (BabbageContextError era) | |
Defined in Cardano.Ledger.Babbage.TxInfo Methods toJSON :: BabbageContextError era -> Value # toEncoding :: BabbageContextError era -> Encoding # toJSONList :: [BabbageContextError era] -> Value # toEncodingList :: [BabbageContextError era] -> Encoding # omitField :: BabbageContextError era -> Bool # | |
(Era era, ToJSON (Datum era), ToJSON (Script era), Val (Value era)) => ToJSON (BabbageTxOut era) | |
Defined in Cardano.Ledger.Babbage.TxOut Methods toJSON :: BabbageTxOut era -> Value # toEncoding :: BabbageTxOut era -> Encoding # toJSONList :: [BabbageTxOut era] -> Value # toEncodingList :: [BabbageTxOut era] -> Encoding # omitField :: BabbageTxOut era -> Bool # | |
ToJSON a => ToJSON (ABlock a) | |
ToJSON a => ToJSON (ABlockOrBoundary a) | |
Defined in Cardano.Chain.Block.Block Methods toJSON :: ABlockOrBoundary a -> Value # toEncoding :: ABlockOrBoundary a -> Encoding # toJSONList :: [ABlockOrBoundary a] -> Value # toEncodingList :: [ABlockOrBoundary a] -> Encoding # omitField :: ABlockOrBoundary a -> Bool # | |
ToJSON a => ToJSON (ABoundaryBlock a) | |
Defined in Cardano.Chain.Block.Block Methods toJSON :: ABoundaryBlock a -> Value # toEncoding :: ABoundaryBlock a -> Encoding # toJSONList :: [ABoundaryBlock a] -> Value # toEncodingList :: [ABoundaryBlock a] -> Encoding # omitField :: ABoundaryBlock a -> Bool # | |
ToJSON a => ToJSON (ABoundaryBody a) | |
Defined in Cardano.Chain.Block.Block Methods toJSON :: ABoundaryBody a -> Value # toEncoding :: ABoundaryBody a -> Encoding # toJSONList :: [ABoundaryBody a] -> Value # toEncodingList :: [ABoundaryBody a] -> Encoding # omitField :: ABoundaryBody a -> Bool # | |
ToJSON a => ToJSON (ABody a) | |
ToJSON a => ToJSON (ABlockSignature a) | |
Defined in Cardano.Chain.Block.Header Methods toJSON :: ABlockSignature a -> Value # toEncoding :: ABlockSignature a -> Encoding # toJSONList :: [ABlockSignature a] -> Value # toEncodingList :: [ABlockSignature a] -> Encoding # omitField :: ABlockSignature a -> Bool # | |
ToJSON a => ToJSON (ABoundaryHeader a) | |
Defined in Cardano.Chain.Block.Header Methods toJSON :: ABoundaryHeader a -> Value # toEncoding :: ABoundaryHeader a -> Encoding # toJSONList :: [ABoundaryHeader a] -> Value # toEncodingList :: [ABoundaryHeader a] -> Encoding # omitField :: ABoundaryHeader a -> Bool # | |
ToJSON a => ToJSON (AHeader a) | |
ToJSON a => ToJSON (Attributes a) | |
Defined in Cardano.Chain.Common.Attributes Methods toJSON :: Attributes a -> Value # toEncoding :: Attributes a -> Encoding # toJSONList :: [Attributes a] -> Value # toEncodingList :: [Attributes a] -> Encoding # omitField :: Attributes a -> Bool # | |
ToJSON a => ToJSON (MerkleRoot a) | |
Defined in Cardano.Chain.Common.Merkle Methods toJSON :: MerkleRoot a -> Value # toEncoding :: MerkleRoot a -> Encoding # toJSONList :: [MerkleRoot a] -> Value # toEncodingList :: [MerkleRoot a] -> Encoding # omitField :: MerkleRoot a -> Bool # | |
ToJSON a => ToJSON (ACertificate a) | |
Defined in Cardano.Chain.Delegation.Certificate Methods toJSON :: ACertificate a -> Value # toEncoding :: ACertificate a -> Encoding # toJSONList :: [ACertificate a] -> Value # toEncodingList :: [ACertificate a] -> Encoding # omitField :: ACertificate a -> Bool # | |
ToJSON a => ToJSON (APayload a) | |
ToJSON a => ToJSON (ATxAux a) | |
ToJSON a => ToJSON (ATxPayload a) | |
Defined in Cardano.Chain.UTxO.TxPayload Methods toJSON :: ATxPayload a -> Value # toEncoding :: ATxPayload a -> Encoding # toJSONList :: [ATxPayload a] -> Value # toEncodingList :: [ATxPayload a] -> Encoding # omitField :: ATxPayload a -> Bool # | |
ToJSON a => ToJSON (APayload a) | |
ToJSON a => ToJSON (AProposal a) | |
ToJSON a => ToJSON (AVote a) | |
(EraPParams era, EraStake era) => ToJSON (ConwayGovState era) | |
Defined in Cardano.Ledger.Conway.Governance Methods toJSON :: ConwayGovState era -> Value # toEncoding :: ConwayGovState era -> Encoding # toJSONList :: [ConwayGovState era] -> Value # toEncodingList :: [ConwayGovState era] -> Encoding # omitField :: ConwayGovState era -> Bool # | |
EraPParams era => ToJSON (PulsingSnapshot era) | |
Defined in Cardano.Ledger.Conway.Governance.DRepPulser Methods toJSON :: PulsingSnapshot era -> Value # toEncoding :: PulsingSnapshot era -> Encoding # toJSONList :: [PulsingSnapshot era] -> Value # toEncodingList :: [PulsingSnapshot era] -> Encoding # omitField :: PulsingSnapshot era -> Bool # | |
EraPParams era => ToJSON (EnactState era) | |
Defined in Cardano.Ledger.Conway.Governance.Internal Methods toJSON :: EnactState era -> Value # toEncoding :: EnactState era -> Encoding # toJSONList :: [EnactState era] -> Value # toEncodingList :: [EnactState era] -> Encoding # omitField :: EnactState era -> Bool # | |
EraPParams era => ToJSON (RatifyState era) | |
Defined in Cardano.Ledger.Conway.Governance.Internal Methods toJSON :: RatifyState era -> Value # toEncoding :: RatifyState era -> Encoding # toJSONList :: [RatifyState era] -> Value # toEncodingList :: [RatifyState era] -> Encoding # omitField :: RatifyState era -> Bool # | |
EraPParams era => ToJSON (Committee era) | |
Era era => ToJSON (Constitution era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: Constitution era -> Value # toEncoding :: Constitution era -> Encoding # toJSONList :: [Constitution era] -> Value # toEncodingList :: [Constitution era] -> Encoding # omitField :: Constitution era -> Bool # | |
EraPParams era => ToJSON (GovAction era) | |
EraPParams era => ToJSON (GovActionState era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionState era -> Value # toEncoding :: GovActionState era -> Encoding # toJSONList :: [GovActionState era] -> Value # toEncodingList :: [GovActionState era] -> Encoding # omitField :: GovActionState era -> Bool # | |
EraPParams era => ToJSON (ProposalProcedure era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: ProposalProcedure era -> Value # toEncoding :: ProposalProcedure era -> Encoding # toJSONList :: [ProposalProcedure era] -> Value # toEncodingList :: [ProposalProcedure era] -> Encoding # omitField :: ProposalProcedure era -> Bool # | |
EraPParams era => ToJSON (VotingProcedure era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: VotingProcedure era -> Value # toEncoding :: VotingProcedure era -> Encoding # toJSONList :: [VotingProcedure era] -> Value # toEncodingList :: [VotingProcedure era] -> Encoding # omitField :: VotingProcedure era -> Bool # | |
EraPParams era => ToJSON (VotingProcedures era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: VotingProcedures era -> Value # toEncoding :: VotingProcedures era -> Encoding # toJSONList :: [VotingProcedures era] -> Value # toEncodingList :: [VotingProcedures era] -> Encoding # omitField :: VotingProcedures era -> Bool # | |
EraPParams era => ToJSON (Proposals era) | |
ToJSON (UpgradeConwayPParams Identity) | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: UpgradeConwayPParams Identity -> Value # toEncoding :: UpgradeConwayPParams Identity -> Encoding # toJSONList :: [UpgradeConwayPParams Identity] -> Value # toEncodingList :: [UpgradeConwayPParams Identity] -> Encoding # | |
ToJSON (ConwayInstantStake era) | |
Defined in Cardano.Ledger.Conway.State.Stake Methods toJSON :: ConwayInstantStake era -> Value # toEncoding :: ConwayInstantStake era -> Encoding # toJSONList :: [ConwayInstantStake era] -> Value # toEncodingList :: [ConwayInstantStake era] -> Encoding # omitField :: ConwayInstantStake era -> Bool # | |
Era era => ToJSON (ConwayTxCert era) | |
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayTxCert era -> Value # toEncoding :: ConwayTxCert era -> Encoding # toJSONList :: [ConwayTxCert era] -> Value # toEncodingList :: [ConwayTxCert era] -> Encoding # omitField :: ConwayTxCert era -> Bool # | |
(ToJSON (TxCert era), ToJSON (PlutusPurpose AsIx era), ToJSON (PlutusPurpose AsItem era), EraPParams era) => ToJSON (ConwayContextError era) | |
Defined in Cardano.Ledger.Conway.TxInfo Methods toJSON :: ConwayContextError era -> Value # toEncoding :: ConwayContextError era -> Encoding # toJSONList :: [ConwayContextError era] -> Value # toEncodingList :: [ConwayContextError era] -> Encoding # omitField :: ConwayContextError era -> Bool # | |
ToJSON a => ToJSON (NonZero a) | |
ToJSON (CommitteeState era) | |
Defined in Cardano.Ledger.CertState Methods toJSON :: CommitteeState era -> Value # toEncoding :: CommitteeState era -> Encoding # toJSONList :: [CommitteeState era] -> Value # toEncodingList :: [CommitteeState era] -> Encoding # omitField :: CommitteeState era -> Bool # | |
ToJSON (DState era) | |
ToJSON (PState era) | |
ToJSON (VState era) | |
ToJSON (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods toJSON :: CompactForm Coin -> Value # toEncoding :: CompactForm Coin -> Encoding # toJSONList :: [CompactForm Coin] -> Value # toEncodingList :: [CompactForm Coin] -> Encoding # omitField :: CompactForm Coin -> Bool # | |
ToJSON (CompactForm DeltaCoin) | |
Defined in Cardano.Ledger.Coin Methods toJSON :: CompactForm DeltaCoin -> Value # toEncoding :: CompactForm DeltaCoin -> Encoding # toJSONList :: [CompactForm DeltaCoin] -> Value # toEncodingList :: [CompactForm DeltaCoin] -> Encoding # omitField :: CompactForm DeltaCoin -> Bool # | |
ToJSON (PParamsHKD Identity era) => ToJSON (PParams era) | |
ToJSON (PParamsHKD StrictMaybe era) => ToJSON (PParamsUpdate era) | |
Defined in Cardano.Ledger.Core.PParams Methods toJSON :: PParamsUpdate era -> Value # toEncoding :: PParamsUpdate era -> Encoding # toJSONList :: [PParamsUpdate era] -> Value # toEncodingList :: [PParamsUpdate era] -> Encoding # omitField :: PParamsUpdate era -> Bool # | |
ToJSON (Credential kr) | |
Defined in Cardano.Ledger.Credential Methods toJSON :: Credential kr -> Value # toEncoding :: Credential kr -> Encoding # toJSONList :: [Credential kr] -> Value # toEncodingList :: [Credential kr] -> Encoding # omitField :: Credential kr -> Bool # | |
ToJSON (KeyHash r) | |
ToJSON (SafeHash i) | |
ToJSON (VRFVerKeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods toJSON :: VRFVerKeyHash r -> Value # toEncoding :: VRFVerKeyHash r -> Encoding # toJSONList :: [VRFVerKeyHash r] -> Value # toEncodingList :: [VRFVerKeyHash r] -> Encoding # omitField :: VRFVerKeyHash r -> Bool # | |
Era era => ToJSON (Datum era) | |
ToJSON a => ToJSON (ExUnits' a) | |
ToJSON (PParams era) => ToJSON (FuturePParams era) | |
Defined in Cardano.Ledger.State.Governance Methods toJSON :: FuturePParams era -> Value # toEncoding :: FuturePParams era -> Encoding # toJSONList :: [FuturePParams era] -> Value # toEncodingList :: [FuturePParams era] -> Encoding # omitField :: FuturePParams era -> Bool # | |
ToJSON (TxOut era) => ToJSON (UTxO era) | |
ToJSON (ShelleyCertState era) | |
Defined in Cardano.Ledger.Shelley.CertState Methods toJSON :: ShelleyCertState era -> Value # toEncoding :: ShelleyCertState era -> Encoding # toJSONList :: [ShelleyCertState era] -> Value # toEncodingList :: [ShelleyCertState era] -> Encoding # omitField :: ShelleyCertState era -> Bool # | |
EraPParams era => ToJSON (ShelleyGovState era) | |
Defined in Cardano.Ledger.Shelley.Governance Methods toJSON :: ShelleyGovState era -> Value # toEncoding :: ShelleyGovState era -> Encoding # toJSONList :: [ShelleyGovState era] -> Value # toEncodingList :: [ShelleyGovState era] -> Encoding # omitField :: ShelleyGovState era -> Bool # | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => ToJSON (EpochState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toJSON :: EpochState era -> Value # toEncoding :: EpochState era -> Encoding # toJSONList :: [EpochState era] -> Value # toEncodingList :: [EpochState era] -> Encoding # omitField :: EpochState era -> Bool # | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => ToJSON (LedgerState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toJSON :: LedgerState era -> Value # toEncoding :: LedgerState era -> Encoding # toJSONList :: [LedgerState era] -> Value # toEncodingList :: [LedgerState era] -> Encoding # omitField :: LedgerState era -> Bool # | |
(EraTxOut era, EraGov era, EraStake era) => ToJSON (UTxOState era) | |
EraPParams era => ToJSON (ProposedPPUpdates era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toJSON :: ProposedPPUpdates era -> Value # toEncoding :: ProposedPPUpdates era -> Encoding # toJSONList :: [ProposedPPUpdates era] -> Value # toEncodingList :: [ProposedPPUpdates era] -> Encoding # omitField :: ProposedPPUpdates era -> Bool # | |
ToJSON (ShelleyInstantStake era) | |
Defined in Cardano.Ledger.Shelley.State.Stake Methods toJSON :: ShelleyInstantStake era -> Value # toEncoding :: ShelleyInstantStake era -> Encoding # toJSONList :: [ShelleyInstantStake era] -> Value # toEncodingList :: [ShelleyInstantStake era] -> Encoding # omitField :: ShelleyInstantStake era -> Bool # | |
ToJSON (TransitionConfig ShelleyEra) | |
Defined in Cardano.Ledger.Shelley.Transition Methods toJSON :: TransitionConfig ShelleyEra -> Value # toEncoding :: TransitionConfig ShelleyEra -> Encoding # toJSONList :: [TransitionConfig ShelleyEra] -> Value # toEncodingList :: [TransitionConfig ShelleyEra] -> Encoding # omitField :: TransitionConfig ShelleyEra -> Bool # | |
Era era => ToJSON (ShelleyTxCert era) | |
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: ShelleyTxCert era -> Value # toEncoding :: ShelleyTxCert era -> Encoding # toJSONList :: [ShelleyTxCert era] -> Value # toEncodingList :: [ShelleyTxCert era] -> Encoding # omitField :: ShelleyTxCert era -> Bool # | |
(Era era, Val (Value era)) => ToJSON (ShelleyTxOut era) | |
Defined in Cardano.Ledger.Shelley.TxOut Methods toJSON :: ShelleyTxOut era -> Value # toEncoding :: ShelleyTxOut era -> Encoding # toJSONList :: [ShelleyTxOut era] -> Value # toEncodingList :: [ShelleyTxOut era] -> Encoding # omitField :: ShelleyTxOut era -> Bool # | |
ToJSON point => ToJSON (FetchDecisionToJSON point) | |
Defined in Cardano.Tracing.OrphanInstances.Network Methods toJSON :: FetchDecisionToJSON point -> Value # toEncoding :: FetchDecisionToJSON point -> Encoding # toJSONList :: [FetchDecisionToJSON point] -> Value # toEncodingList :: [FetchDecisionToJSON point] -> Encoding # omitField :: FetchDecisionToJSON point -> Bool # | |
(ToJSON peer, ToJSON (Verbose point)) => ToJSON (Verbose (TraceLabelPeer peer (FetchDecision [point]))) | |
Defined in Cardano.Tracing.OrphanInstances.Network Methods toJSON :: Verbose (TraceLabelPeer peer (FetchDecision [point])) -> Value # toEncoding :: Verbose (TraceLabelPeer peer (FetchDecision [point])) -> Encoding # toJSONList :: [Verbose (TraceLabelPeer peer (FetchDecision [point]))] -> Value # toEncodingList :: [Verbose (TraceLabelPeer peer (FetchDecision [point]))] -> Encoding # omitField :: Verbose (TraceLabelPeer peer (FetchDecision [point])) -> Bool # | |
ConvertRawHash header => ToJSON (Verbose (Point header)) | |
Defined in Cardano.Tracing.OrphanInstances.Network | |
ToJSON a => ToJSON (WithOrigin a) | |
Defined in Cardano.Slotting.Slot Methods toJSON :: WithOrigin a -> Value # toEncoding :: WithOrigin a -> Encoding # toJSONList :: [WithOrigin a] -> Value # toEncodingList :: [WithOrigin a] -> Encoding # omitField :: WithOrigin a -> Bool # | |
ToJSON a => ToJSON (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods toJSON :: StrictMaybe a -> Value # toEncoding :: StrictMaybe a -> Encoding # toJSONList :: [StrictMaybe a] -> Value # toEncodingList :: [StrictMaybe a] -> Encoding # omitField :: StrictMaybe a -> Bool # | |
ToJSON a => ToJSON (StrictSeq a) | |
ToJSON a => ToJSON (IntMap a) | |
ToJSON a => ToJSON (Seq a) | |
ToJSON a => ToJSON (Set a) | |
ToJSON v => ToJSON (Tree v) | |
ToJSON1 f => ToJSON (Fix f) | Since: aeson-1.5.3.0 |
(ToJSON1 f, Functor f) => ToJSON (Mu f) | Since: aeson-1.5.3.0 |
(ToJSON1 f, Functor f) => ToJSON (Nu f) | Since: aeson-1.5.3.0 |
ToJSON a => ToJSON (DNonEmpty a) | Since: aeson-1.5.3.0 |
ToJSON a => ToJSON (DList a) | |
ToJSON a => ToJSON (NonEmpty a) | |
ToJSON a => ToJSON (Identity a) | |
ToJSON a => ToJSON (First a) | |
ToJSON a => ToJSON (Last a) | |
ToJSON a => ToJSON (Down a) | Since: aeson-2.2.0.0 |
ToJSON a => ToJSON (Dual a) | |
ToJSON a => ToJSON (Product a) | Since: aeson-2.2.3.0 |
ToJSON a => ToJSON (Sum a) | Since: aeson-2.2.3.0 |
(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a) | Since: aeson-2.1.0.0 |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: Generically a -> Value # toEncoding :: Generically a -> Encoding # toJSONList :: [Generically a] -> Value # toEncodingList :: [Generically a] -> Encoding # omitField :: Generically a -> Bool # | |
(ToJSON a, Integral a) => ToJSON (Ratio a) | |
ToJSON a => ToJSON (InsOrdHashSet a) | |
Defined in Data.HashSet.InsOrd Methods toJSON :: InsOrdHashSet a -> Value # toEncoding :: InsOrdHashSet a -> Encoding # toJSONList :: [InsOrdHashSet a] -> Value # toEncodingList :: [InsOrdHashSet a] -> Encoding # omitField :: InsOrdHashSet a -> Bool # | |
ToJSON a => ToJSON (LOContent a) | |
ToJSON a => ToJSON (LogObject a) | |
ToJSON a => ToJSON (Resources a) | |
ToJSON a => ToJSON (Item a) | |
ToJSON (Bech32StringOf a) | |
Defined in Maestro.Types.Common Methods toJSON :: Bech32StringOf a -> Value # toEncoding :: Bech32StringOf a -> Encoding # toJSONList :: [Bech32StringOf a] -> Value # toEncodingList :: [Bech32StringOf a] -> Encoding # omitField :: Bech32StringOf a -> Bool # | |
ToJSON (HashStringOf a) | |
Defined in Maestro.Types.Common Methods toJSON :: HashStringOf a -> Value # toEncoding :: HashStringOf a -> Encoding # toJSONList :: [HashStringOf a] -> Value # toEncodingList :: [HashStringOf a] -> Encoding # omitField :: HashStringOf a -> Bool # | |
ToJSON (HexStringOf a) | |
Defined in Maestro.Types.Common Methods toJSON :: HexStringOf a -> Value # toEncoding :: HexStringOf a -> Encoding # toJSONList :: [HexStringOf a] -> Value # toEncodingList :: [HexStringOf a] -> Encoding # omitField :: HexStringOf a -> Bool # | |
ToJSON (TaggedText description) | |
Defined in Maestro.Types.V1.Common Methods toJSON :: TaggedText description -> Value # toEncoding :: TaggedText description -> Encoding # toJSONList :: [TaggedText description] -> Value # toEncodingList :: [TaggedText description] -> Encoding # omitField :: TaggedText description -> Bool # | |
ToJSON i => ToJSON (MemoryCpuWith i) | |
Defined in Maestro.Types.V1.General Methods toJSON :: MemoryCpuWith i -> Value # toEncoding :: MemoryCpuWith i -> Encoding # toJSONList :: [MemoryCpuWith i] -> Value # toEncodingList :: [MemoryCpuWith i] -> Encoding # omitField :: MemoryCpuWith i -> Bool # | |
(Eq p, ToJSON p, AesonDefaultValue p) => ToJSON (OAuth2Flow p) | |
Defined in Data.OpenApi.Internal Methods toJSON :: OAuth2Flow p -> Value # toEncoding :: OAuth2Flow p -> Encoding # toJSONList :: [OAuth2Flow p] -> Value # toEncodingList :: [OAuth2Flow p] -> Encoding # omitField :: OAuth2Flow p -> Bool # | |
ToJSON (Referenced Callback) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Callback -> Value # toEncoding :: Referenced Callback -> Encoding # toJSONList :: [Referenced Callback] -> Value # toEncodingList :: [Referenced Callback] -> Encoding # omitField :: Referenced Callback -> Bool # | |
ToJSON (Referenced Example) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Example -> Value # toEncoding :: Referenced Example -> Encoding # toJSONList :: [Referenced Example] -> Value # toEncodingList :: [Referenced Example] -> Encoding # omitField :: Referenced Example -> Bool # | |
ToJSON (Referenced Header) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Header -> Value # toEncoding :: Referenced Header -> Encoding # toJSONList :: [Referenced Header] -> Value # toEncodingList :: [Referenced Header] -> Encoding # omitField :: Referenced Header -> Bool # | |
ToJSON (Referenced Link) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Link -> Value # toEncoding :: Referenced Link -> Encoding # toJSONList :: [Referenced Link] -> Value # toEncodingList :: [Referenced Link] -> Encoding # omitField :: Referenced Link -> Bool # | |
ToJSON (Referenced Param) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Param -> Value # toEncoding :: Referenced Param -> Encoding # toJSONList :: [Referenced Param] -> Value # toEncodingList :: [Referenced Param] -> Encoding # omitField :: Referenced Param -> Bool # | |
ToJSON (Referenced RequestBody) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced RequestBody -> Value # toEncoding :: Referenced RequestBody -> Encoding # toJSONList :: [Referenced RequestBody] -> Value # toEncodingList :: [Referenced RequestBody] -> Encoding # omitField :: Referenced RequestBody -> Bool # | |
ToJSON (Referenced Response) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Response -> Value # toEncoding :: Referenced Response -> Encoding # toJSONList :: [Referenced Response] -> Value # toEncodingList :: [Referenced Response] -> Encoding # omitField :: Referenced Response -> Bool # | |
ToJSON (Referenced Schema) | |
Defined in Data.OpenApi.Internal Methods toJSON :: Referenced Schema -> Value # toEncoding :: Referenced Schema -> Encoding # toJSONList :: [Referenced Schema] -> Value # toEncodingList :: [Referenced Schema] -> Encoding # omitField :: Referenced Schema -> Bool # | |
ToJSON (BuiltinCostModelBase MCostingFun) | |
Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel Methods toJSON :: BuiltinCostModelBase MCostingFun -> Value # toEncoding :: BuiltinCostModelBase MCostingFun -> Encoding # toJSONList :: [BuiltinCostModelBase MCostingFun] -> Value # toEncodingList :: [BuiltinCostModelBase MCostingFun] -> Encoding # | |
ToJSON (BuiltinCostModelBase CostingFun) | |
Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel Methods toJSON :: BuiltinCostModelBase CostingFun -> Value # toEncoding :: BuiltinCostModelBase CostingFun -> Encoding # toJSONList :: [BuiltinCostModelBase CostingFun] -> Value # toEncodingList :: [BuiltinCostModelBase CostingFun] -> Encoding # | |
ToJSON a => ToJSON (MCostingFun a) | |
Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel Methods toJSON :: MCostingFun a -> Value # toEncoding :: MCostingFun a -> Encoding # toJSONList :: [MCostingFun a] -> Value # toEncodingList :: [MCostingFun a] -> Encoding # omitField :: MCostingFun a -> Bool # | |
ToJSON (CekMachineCostsBase Identity) | |
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts Methods toJSON :: CekMachineCostsBase Identity -> Value # toEncoding :: CekMachineCostsBase Identity -> Encoding # toJSONList :: [CekMachineCostsBase Identity] -> Value # toEncodingList :: [CekMachineCostsBase Identity] -> Encoding # | |
ToJSON (CekMachineCostsBase Maybe) | |
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts Methods toJSON :: CekMachineCostsBase Maybe -> Value # toEncoding :: CekMachineCostsBase Maybe -> Encoding # toJSONList :: [CekMachineCostsBase Maybe] -> Value # toEncodingList :: [CekMachineCostsBase Maybe] -> Encoding # omitField :: CekMachineCostsBase Maybe -> Bool # | |
ToJSON (ArgumentBlueprint referencedTypes) | |
Defined in PlutusTx.Blueprint.Argument Methods toJSON :: ArgumentBlueprint referencedTypes -> Value # toEncoding :: ArgumentBlueprint referencedTypes -> Encoding # toJSONList :: [ArgumentBlueprint referencedTypes] -> Value # toEncodingList :: [ArgumentBlueprint referencedTypes] -> Encoding # omitField :: ArgumentBlueprint referencedTypes -> Bool # | |
ToJSON (ParameterBlueprint referencedTypes) | |
Defined in PlutusTx.Blueprint.Parameter Methods toJSON :: ParameterBlueprint referencedTypes -> Value # toEncoding :: ParameterBlueprint referencedTypes -> Encoding # toJSONList :: [ParameterBlueprint referencedTypes] -> Value # toEncodingList :: [ParameterBlueprint referencedTypes] -> Encoding # omitField :: ParameterBlueprint referencedTypes -> Bool # | |
ToJSON (Schema referencedTypes) | |
ToJSON (ValidatorBlueprint referencedTypes) | |
Defined in PlutusTx.Blueprint.Validator Methods toJSON :: ValidatorBlueprint referencedTypes -> Value # toEncoding :: ValidatorBlueprint referencedTypes -> Encoding # toJSONList :: [ValidatorBlueprint referencedTypes] -> Value # toEncodingList :: [ValidatorBlueprint referencedTypes] -> Encoding # omitField :: ValidatorBlueprint referencedTypes -> Bool # | |
ToJSON a => ToJSON (Array a) | |
(Prim a, ToJSON a) => ToJSON (PrimArray a) | |
ToJSON a => ToJSON (SmallArray a) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: SmallArray a -> Value # toEncoding :: SmallArray a -> Encoding # toJSONList :: [SmallArray a] -> Value # toEncodingList :: [SmallArray a] -> Encoding # omitField :: SmallArray a -> Bool # | |
ToJSON d => ToJSON (LinearTransform d) | |
Defined in Statistics.Distribution.Transform Methods toJSON :: LinearTransform d -> Value # toEncoding :: LinearTransform d -> Encoding # toJSONList :: [LinearTransform d] -> Value # toEncodingList :: [LinearTransform d] -> Encoding # omitField :: LinearTransform d -> Bool # | |
ToJSON a => ToJSON (Maybe a) | Since: aeson-1.5.3.0 |
ToJSON (CollectionFormat t) | |
Defined in Data.Swagger.Internal Methods toJSON :: CollectionFormat t -> Value # toEncoding :: CollectionFormat t -> Encoding # toJSONList :: [CollectionFormat t] -> Value # toEncodingList :: [CollectionFormat t] -> Encoding # omitField :: CollectionFormat t -> Bool # | |
ToJSON (ParamSchema k) | |
Defined in Data.Swagger.Internal Methods toJSON :: ParamSchema k -> Value # toEncoding :: ParamSchema k -> Encoding # toJSONList :: [ParamSchema k] -> Value # toEncodingList :: [ParamSchema k] -> Encoding # omitField :: ParamSchema k -> Bool # | |
ToJSON (Referenced Param) | |
Defined in Data.Swagger.Internal Methods toJSON :: Referenced Param -> Value # toEncoding :: Referenced Param -> Encoding # toJSONList :: [Referenced Param] -> Value # toEncodingList :: [Referenced Param] -> Encoding # omitField :: Referenced Param -> Bool # | |
ToJSON (Referenced Response) | |
Defined in Data.Swagger.Internal Methods toJSON :: Referenced Response -> Value # toEncoding :: Referenced Response -> Encoding # toJSONList :: [Referenced Response] -> Value # toEncodingList :: [Referenced Response] -> Encoding # omitField :: Referenced Response -> Bool # | |
ToJSON (Referenced Schema) | |
Defined in Data.Swagger.Internal Methods toJSON :: Referenced Schema -> Value # toEncoding :: Referenced Schema -> Encoding # toJSONList :: [Referenced Schema] -> Value # toEncodingList :: [Referenced Schema] -> Encoding # omitField :: Referenced Schema -> Bool # | |
ToJSON (ParamSchema t) => ToJSON (SwaggerItems t) | As for nullary schema for 0-arity type constructors, see https://github.com/GetShopTV/swagger2/issues/167.
|
Defined in Data.Swagger.Internal Methods toJSON :: SwaggerItems t -> Value # toEncoding :: SwaggerItems t -> Encoding # toJSONList :: [SwaggerItems t] -> Value # toEncodingList :: [SwaggerItems t] -> Encoding # omitField :: SwaggerItems t -> Bool # | |
ToJSON (SwaggerType t) | |
Defined in Data.Swagger.Internal Methods toJSON :: SwaggerType t -> Value # toEncoding :: SwaggerType t -> Encoding # toJSONList :: [SwaggerType t] -> Value # toEncodingList :: [SwaggerType t] -> Encoding # omitField :: SwaggerType t -> Bool # | |
ToJSON a => ToJSON (HashSet a) | |
ToJSON a => ToJSON (Vector a) | |
(Prim a, ToJSON a) => ToJSON (Vector a) | |
(Storable a, ToJSON a) => ToJSON (Vector a) | |
(Vector Vector a, ToJSON a) => ToJSON (Vector a) | |
ToJSON a => ToJSON (Maybe a) | |
ToJSON a => ToJSON (Solo a) | Since: aeson-2.0.2.0 |
ToJSON a => ToJSON [a] | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: [a] -> Encoding # toJSONList :: [[a]] -> Value # toEncodingList :: [[a]] -> Encoding # | |
HasResolution a => ToJSON (Fixed a) | |
ToJSON (File content direction) | |
ToJSON (ScriptLanguageInEra lang era) | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptLanguageInEra lang era -> Value # toEncoding :: ScriptLanguageInEra lang era -> Encoding # toJSONList :: [ScriptLanguageInEra lang era] -> Value # toEncodingList :: [ScriptLanguageInEra lang era] -> Encoding # omitField :: ScriptLanguageInEra lang era -> Bool # | |
IsCardanoEra era => ToJSON (TxOut ctx era) | |
HashAlgorithm h => ToJSON (Hash h a) | |
ToJSON (AbstractHash algo a) | |
Defined in Cardano.Crypto.Hashing Methods toJSON :: AbstractHash algo a -> Value # toEncoding :: AbstractHash algo a -> Encoding # toJSONList :: [AbstractHash algo a] -> Value # toEncodingList :: [AbstractHash algo a] -> Encoding # omitField :: AbstractHash algo a -> Bool # | |
(ToJSON v, ToJSONKey k) => ToJSON (ListMap k v) | |
(HasOKey k v, ToJSON v) => ToJSON (OMap k v) | |
ToJSON (AlonzoPParams StrictMaybe AlonzoEra) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: AlonzoPParams StrictMaybe AlonzoEra -> Value # toEncoding :: AlonzoPParams StrictMaybe AlonzoEra -> Encoding # toJSONList :: [AlonzoPParams StrictMaybe AlonzoEra] -> Value # toEncodingList :: [AlonzoPParams StrictMaybe AlonzoEra] -> Encoding # | |
ToJSON (AlonzoPParams Identity AlonzoEra) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: AlonzoPParams Identity AlonzoEra -> Value # toEncoding :: AlonzoPParams Identity AlonzoEra -> Encoding # toJSONList :: [AlonzoPParams Identity AlonzoEra] -> Value # toEncodingList :: [AlonzoPParams Identity AlonzoEra] -> Encoding # | |
ToJSON (AlonzoContextError era) | |
Defined in Cardano.Ledger.Alonzo.Plutus.TxInfo Methods toJSON :: AlonzoContextError era -> Value # toEncoding :: AlonzoContextError era -> Encoding # toJSONList :: [AlonzoContextError era] -> Value # toEncodingList :: [AlonzoContextError era] -> Encoding # omitField :: AlonzoContextError era -> Bool # | |
(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), Era era) => ToJSON (AlonzoPlutusPurpose f era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods toJSON :: AlonzoPlutusPurpose f era -> Value # toEncoding :: AlonzoPlutusPurpose f era -> Encoding # toJSONList :: [AlonzoPlutusPurpose f era] -> Value # toEncodingList :: [AlonzoPlutusPurpose f era] -> Encoding # omitField :: AlonzoPlutusPurpose f era -> Bool # | |
ToJSON it => ToJSON (AsItem ix it) | |
ToJSON ix => ToJSON (AsIx ix it) | |
(ToJSON ix, ToJSON it) => ToJSON (AsIxItem ix it) | |
(PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: BabbagePParams StrictMaybe era -> Value # toEncoding :: BabbagePParams StrictMaybe era -> Encoding # toJSONList :: [BabbagePParams StrictMaybe era] -> Value # toEncodingList :: [BabbagePParams StrictMaybe era] -> Encoding # omitField :: BabbagePParams StrictMaybe era -> Bool # | |
(PParamsHKD Identity era ~ BabbagePParams Identity era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams Identity era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: BabbagePParams Identity era -> Value # toEncoding :: BabbagePParams Identity era -> Encoding # toJSONList :: [BabbagePParams Identity era] -> Value # toEncodingList :: [BabbagePParams Identity era] -> Encoding # omitField :: BabbagePParams Identity era -> Bool # | |
ToJSON b => ToJSON (Annotated b a) | |
Era era => ToJSON (GovPurposeId p era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovPurposeId p era -> Value # toEncoding :: GovPurposeId p era -> Encoding # toJSONList :: [GovPurposeId p era] -> Value # toEncodingList :: [GovPurposeId p era] -> Encoding # omitField :: GovPurposeId p era -> Bool # | |
(Era era, forall (p :: GovActionPurpose). ToJSON (f (GovPurposeId p era))) => ToJSON (GovRelation f era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovRelation f era -> Value # toEncoding :: GovRelation f era -> Encoding # toJSONList :: [GovRelation f era] -> Value # toEncodingList :: [GovRelation f era] -> Encoding # omitField :: GovRelation f era -> Bool # | |
(ConwayEraPParams era, PParamsHKD StrictMaybe era ~ ConwayPParams StrictMaybe era) => ToJSON (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: ConwayPParams StrictMaybe era -> Value # toEncoding :: ConwayPParams StrictMaybe era -> Encoding # toJSONList :: [ConwayPParams StrictMaybe era] -> Value # toEncodingList :: [ConwayPParams StrictMaybe era] -> Encoding # omitField :: ConwayPParams StrictMaybe era -> Bool # | |
ToJSON (ConwayPParams Identity ConwayEra) | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: ConwayPParams Identity ConwayEra -> Value # toEncoding :: ConwayPParams Identity ConwayEra -> Encoding # toJSONList :: [ConwayPParams Identity ConwayEra] -> Value # toEncodingList :: [ConwayPParams Identity ConwayEra] -> Encoding # | |
(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), EraPParams era) => ToJSON (ConwayPlutusPurpose f era) | |
Defined in Cardano.Ledger.Conway.Scripts Methods toJSON :: ConwayPlutusPurpose f era -> Value # toEncoding :: ConwayPlutusPurpose f era -> Encoding # toJSONList :: [ConwayPlutusPurpose f era] -> Value # toEncodingList :: [ConwayPlutusPurpose f era] -> Encoding # omitField :: ConwayPlutusPurpose f era -> Bool # | |
Bounded (BoundedRatio b Word64) => ToJSON (BoundedRatio b Word64) | |
ToJSON a => ToJSON (Mismatch r a) | |
(EraPParams era, PParamsHKD StrictMaybe era ~ ShelleyPParams StrictMaybe era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toJSON :: ShelleyPParams StrictMaybe era -> Value # toEncoding :: ShelleyPParams StrictMaybe era -> Encoding # toJSONList :: [ShelleyPParams StrictMaybe era] -> Value # toEncodingList :: [ShelleyPParams StrictMaybe era] -> Encoding # omitField :: ShelleyPParams StrictMaybe era -> Bool # | |
(EraPParams era, PParamsHKD Identity era ~ ShelleyPParams Identity era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams Identity era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toJSON :: ShelleyPParams Identity era -> Value # toEncoding :: ShelleyPParams Identity era -> Encoding # toJSONList :: [ShelleyPParams Identity era] -> Value # toEncodingList :: [ShelleyPParams Identity era] -> Encoding # omitField :: ShelleyPParams Identity era -> Bool # | |
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
ToJSON (Proxy a) | |
(ToJSONKey k, ToJSON v) => ToJSON (InsOrdHashMap k v) | |
Defined in Data.HashMap.Strict.InsOrd Methods toJSON :: InsOrdHashMap k v -> Value # toEncoding :: InsOrdHashMap k v -> Encoding # toJSONList :: [InsOrdHashMap k v] -> Value # toEncodingList :: [InsOrdHashMap k v] -> Encoding # omitField :: InsOrdHashMap k v -> Bool # | |
(ToJSON a, ToJSONKey k) => ToJSON (MonoidalMap k a) | |
Defined in Data.Map.Monoidal Methods toJSON :: MonoidalMap k a -> Value # toEncoding :: MonoidalMap k a -> Encoding # toJSONList :: [MonoidalMap k a] -> Value # toEncodingList :: [MonoidalMap k a] -> Encoding # omitField :: MonoidalMap k a -> Bool # | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | Since: aeson-1.5.3.0 |
(ToJSON a, ToJSON b) => ToJSON (These a b) | Since: aeson-1.5.3.0 |
(ToJSON a, ToJSON b) => ToJSON (Pair a b) | Since: aeson-1.5.3.0 |
(ToJSON a, ToJSON b) => ToJSON (These a b) | Since: aeson-1.5.1.0 |
(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) | |
ToJSON (Address, NutlinkTicker) | |
Defined in Blockfrost.Types.NutLink Methods toJSON :: (Address, NutlinkTicker) -> Value # toEncoding :: (Address, NutlinkTicker) -> Encoding # toJSONList :: [(Address, NutlinkTicker)] -> Value # toEncodingList :: [(Address, NutlinkTicker)] -> Encoding # omitField :: (Address, NutlinkTicker) -> Bool # | |
ToJSON (Text, Metric) | |
(ToJSON a, ToJSON b) => ToJSON (a, b) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: (a, b) -> Encoding # toJSONList :: [(a, b)] -> Value # toEncodingList :: [(a, b)] -> Encoding # | |
(Typeable t, ToJSON a) => ToJSON (THKD t StrictMaybe a) | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: THKD t StrictMaybe a -> Value # toEncoding :: THKD t StrictMaybe a -> Encoding # toJSONList :: [THKD t StrictMaybe a] -> Value # toEncodingList :: [THKD t StrictMaybe a] -> Encoding # omitField :: THKD t StrictMaybe a -> Bool # | |
(Typeable t, ToJSON a) => ToJSON (THKD t Identity a) | |
(AesonOptions t, Generic a, GToJSON Zero (Rep a), GToEncoding Zero (Rep a)) => ToJSON (CustomJSON t a) | |
Defined in Deriving.Aeson Methods toJSON :: CustomJSON t a -> Value # toEncoding :: CustomJSON t a -> Encoding # toJSONList :: [CustomJSON t a] -> Value # toEncodingList :: [CustomJSON t a] -> Encoding # omitField :: CustomJSON t a -> Bool # | |
ToJSON a => ToJSON (Const a b) | |
ToJSON b => ToJSON (Tagged a b) | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a) | Since: aeson-1.5.1.0 |
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c) -> Value # toEncoding :: (a, b, c) -> Encoding # toJSONList :: [(a, b, c)] -> Value # toEncodingList :: [(a, b, c)] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) | |
(Vector vk k, Vector vv v, ToJSONKey k, ToJSON v) => ToJSON (VMap vk vv k v) | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d) -> Value # toEncoding :: (a, b, c, d) -> Encoding # toJSONList :: [(a, b, c, d)] -> Value # toEncodingList :: [(a, b, c, d)] -> Encoding # | |
(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e) -> Value # toEncoding :: (a, b, c, d, e) -> Encoding # toJSONList :: [(a, b, c, d, e)] -> Value # toEncodingList :: [(a, b, c, d, e)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f) -> Value # toEncoding :: (a, b, c, d, e, f) -> Encoding # toJSONList :: [(a, b, c, d, e, f)] -> Value # toEncodingList :: [(a, b, c, d, e, f)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g) -> Value # toEncoding :: (a, b, c, d, e, f, g) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h) -> Value # toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # | |
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in Data.Aeson.Types.ToJSON Methods toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value # toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding # toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value # toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding # omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # |
A type that can be converted from JSON, with the possibility of failure.
In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.
There are various reasons a conversion could fail. For example, an
Object
could be missing a required key, an Array
could be of
the wrong size, or a value could be of an incompatible type.
The basic ways to signal a failed conversion are as follows:
fail
yields a custom error message: it is the recommended way of reporting a failure;empty
(ormzero
) is uninformative: use it when the error is meant to be caught by some(
;<|>
)typeMismatch
can be used to report a failure when the encountered value is not of the expected JSON type;unexpected
is an appropriate alternative when more than one type may be expected, or to keep the expected type implicit.
prependFailure
(or modifyFailure
) add more information to a parser's
error messages.
An example type and instance using typeMismatch
and prependFailure
:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceFromJSON
Coord whereparseJSON
(Object
v) = Coord<$>
v.:
"x"<*>
v.:
"y" -- We do not expect a non-Object
value here. -- We could useempty
to fail, buttypeMismatch
-- gives a much more informative error message.parseJSON
invalid =prependFailure
"parsing Coord failed, " (typeMismatch
"Object" invalid)
For this common case of only being concerned with a single
type of JSON value, the functions withObject
, withScientific
, etc.
are provided. Their use is to be preferred when possible, since
they are more terse. Using withObject
, we can rewrite the above instance
(assuming the same language extension and data type) as:
instanceFromJSON
Coord whereparseJSON
=withObject
"Coord" $ \v -> Coord<$>
v.:
"x"<*>
v.:
"y"
Instead of manually writing your FromJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
parseJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
FromJSON
instance for your datatype without giving
a definition for parseJSON
.
For example, the previous example can be simplified to just:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceFromJSON
Coord
or using the DerivingVia extension
deriving viaGenerically
Coord instanceFromJSON
Coord
The default implementation will be equivalent to
parseJSON =
; if you need different
options, you can customize the generic decoding by defining:genericParseJSON
defaultOptions
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceFromJSON
Coord whereparseJSON
=genericParseJSON
customOptions
Minimal complete definition
Nothing
Methods
parseJSON :: Value -> Parser a #
parseJSONList :: Value -> Parser [a] #
omittedField :: Maybe a #
Default value for optional fields.
Used by (
operator, and Generics and TH deriving
with .:?=
)
(default).allowOmittedFields
= True
Since: aeson-2.2.0.0
Instances
FromJSON Key | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON DotNetTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Value | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON GYCoreConfig # | |
Defined in GeniusYield.GYConfig | |
FromJSON GYCoreProviderInfo # | |
Defined in GeniusYield.GYConfig Methods parseJSON :: Value -> Parser GYCoreProviderInfo # parseJSONList :: Value -> Parser [GYCoreProviderInfo] # | |
FromJSON GYAddress # | In JSON context addresses are represented in hex.
|
Defined in GeniusYield.Types.Address | |
FromJSON GYAddressBech32 # |
|
Defined in GeniusYield.Types.Address Methods parseJSON :: Value -> Parser GYAddressBech32 # parseJSONList :: Value -> Parser [GYAddressBech32] # | |
FromJSON GYStakeAddress # | In JSON context, stake addresses are represented in hex.
|
Defined in GeniusYield.Types.Address Methods parseJSON :: Value -> Parser GYStakeAddress # parseJSONList :: Value -> Parser [GYStakeAddress] # | |
FromJSON GYStakeAddressBech32 # |
|
Defined in GeniusYield.Types.Address Methods parseJSON :: Value -> Parser GYStakeAddressBech32 # parseJSONList :: Value -> Parser [GYStakeAddressBech32] # | |
FromJSON GYAnchorDataHash # | |
Defined in GeniusYield.Types.Anchor Methods parseJSON :: Value -> Parser GYAnchorDataHash # parseJSONList :: Value -> Parser [GYAnchorDataHash] # | |
FromJSON GYUrl # | |
Defined in GeniusYield.Types.Anchor | |
FromJSON ArgumentBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Argument Methods parseJSON :: Value -> Parser ArgumentBlueprint # parseJSONList :: Value -> Parser [ArgumentBlueprint] # | |
FromJSON ContractBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Contract Methods parseJSON :: Value -> Parser ContractBlueprint # parseJSONList :: Value -> Parser [ContractBlueprint] # | |
FromJSON DefinitionId # | |
Defined in GeniusYield.Types.Blueprint.DefinitionId | |
FromJSON ParameterBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Parameter Methods parseJSON :: Value -> Parser ParameterBlueprint # parseJSONList :: Value -> Parser [ParameterBlueprint] # | |
FromJSON Preamble # | |
Defined in GeniusYield.Types.Blueprint.Preamble | |
FromJSON Purpose # | |
Defined in GeniusYield.Types.Blueprint.Purpose | |
FromJSON BytesSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema | |
FromJSON ConstructorSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema Methods parseJSON :: Value -> Parser ConstructorSchema # parseJSONList :: Value -> Parser [ConstructorSchema] # | |
FromJSON IntegerSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema Methods parseJSON :: Value -> Parser IntegerSchema # parseJSONList :: Value -> Parser [IntegerSchema] # | |
FromJSON ListSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema | |
FromJSON MapSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema | |
FromJSON PairSchema # | |
Defined in GeniusYield.Types.Blueprint.Schema | |
FromJSON Schema # | |
Defined in GeniusYield.Types.Blueprint.Schema | |
FromJSON ValidatorBlueprint # | |
Defined in GeniusYield.Types.Blueprint.Validator Methods parseJSON :: Value -> Parser ValidatorBlueprint # parseJSONList :: Value -> Parser [ValidatorBlueprint] # | |
FromJSON GYDatum # | Datums use cardano-api's detailed schema for JSON representation.
|
Defined in GeniusYield.Types.Datum | |
FromJSON GYDatumHash # | |
Defined in GeniusYield.Types.Datum | |
FromJSON GYLogScribeConfig # |
|
Defined in GeniusYield.Types.Logging Methods parseJSON :: Value -> Parser GYLogScribeConfig # parseJSONList :: Value -> Parser [GYLogScribeConfig] # | |
FromJSON GYLogScribeType # |
|
Defined in GeniusYield.Types.Logging Methods parseJSON :: Value -> Parser GYLogScribeType # parseJSONList :: Value -> Parser [GYLogScribeType] # | |
FromJSON GYLogSeverity # |
|
Defined in GeniusYield.Types.Logging Methods parseJSON :: Value -> Parser GYLogSeverity # parseJSONList :: Value -> Parser [GYLogSeverity] # | |
FromJSON GYLogVerbosity # | |
Defined in GeniusYield.Types.Logging Methods parseJSON :: Value -> Parser GYLogVerbosity # parseJSONList :: Value -> Parser [GYLogVerbosity] # | |
FromJSON LogSrc # | |
Defined in GeniusYield.Types.Logging | |
FromJSON GYNatural # |
|
Defined in GeniusYield.Types.Natural | |
FromJSON GYNetworkId # |
|
Defined in GeniusYield.Types.NetworkId | |
FromJSON GYNetworkInfo # | |
Defined in GeniusYield.Types.NetworkId Methods parseJSON :: Value -> Parser GYNetworkInfo # parseJSONList :: Value -> Parser [GYNetworkInfo] # | |
FromJSON GYPubKeyHash # |
Invalid characters:
|
Defined in GeniusYield.Types.PubKeyHash | |
FromJSON GYRational # |
|
Defined in GeniusYield.Types.Rational | |
FromJSON GYMintingPolicyId # | |
Defined in GeniusYield.Types.Script Methods parseJSON :: Value -> Parser GYMintingPolicyId # parseJSONList :: Value -> Parser [GYMintingPolicyId] # | |
FromJSON GYScriptHash # | |
Defined in GeniusYield.Types.Script.ScriptHash | |
FromJSON GYSimpleScript # | |
Defined in GeniusYield.Types.Script.SimpleScript Methods parseJSON :: Value -> Parser GYSimpleScript # parseJSONList :: Value -> Parser [GYSimpleScript] # | |
FromJSON GYSlot # | |
Defined in GeniusYield.Types.Slot | |
FromJSON GYStakePoolIdBech32 # |
|
Defined in GeniusYield.Types.StakePoolId Methods parseJSON :: Value -> Parser GYStakePoolIdBech32 # parseJSONList :: Value -> Parser [GYStakePoolIdBech32] # | |
FromJSON GYTime # |
|
Defined in GeniusYield.Types.Time | |
FromJSON GYTx # |
|
Defined in GeniusYield.Types.Tx | |
FromJSON GYTxId # | |
Defined in GeniusYield.Types.Tx | |
FromJSON GYTxWitness # | |
Defined in GeniusYield.Types.Tx | |
FromJSON GYTxOutRef # | |
Defined in GeniusYield.Types.TxOutRef | |
FromJSON GYTxOutRefCbor # | |
Defined in GeniusYield.Types.TxOutRef Methods parseJSON :: Value -> Parser GYTxOutRefCbor # parseJSONList :: Value -> Parser [GYTxOutRefCbor] # | |
FromJSON GYAssetClass # |
|
Defined in GeniusYield.Types.Value | |
FromJSON GYTokenName # |
|
Defined in GeniusYield.Types.Value | |
FromJSON GYValue # |
|
Defined in GeniusYield.Types.Value | |
FromJSON ByteString64 | |
Defined in Data.ByteString.Base64.Type | |
FromJSON ApiError | |
Defined in Blockfrost.Types.ApiError | |
FromJSON AccountDelegation | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountDelegation # parseJSONList :: Value -> Parser [AccountDelegation] # | |
FromJSON AccountHistory | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountHistory # parseJSONList :: Value -> Parser [AccountHistory] # | |
FromJSON AccountInfo | |
Defined in Blockfrost.Types.Cardano.Accounts | |
FromJSON AccountMir | |
Defined in Blockfrost.Types.Cardano.Accounts | |
FromJSON AccountRegistration | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountRegistration # parseJSONList :: Value -> Parser [AccountRegistration] # | |
FromJSON AccountRegistrationAction | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountRegistrationAction # parseJSONList :: Value -> Parser [AccountRegistrationAction] # | |
FromJSON AccountReward | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountReward # parseJSONList :: Value -> Parser [AccountReward] # | |
FromJSON AccountWithdrawal | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AccountWithdrawal # parseJSONList :: Value -> Parser [AccountWithdrawal] # | |
FromJSON AddressAssociated | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AddressAssociated # parseJSONList :: Value -> Parser [AddressAssociated] # | |
FromJSON AddressAssociatedTotal | |
Defined in Blockfrost.Types.Cardano.Accounts Methods parseJSON :: Value -> Parser AddressAssociatedTotal # parseJSONList :: Value -> Parser [AddressAssociatedTotal] # | |
FromJSON RewardType | |
Defined in Blockfrost.Types.Cardano.Accounts | |
FromJSON AddressDetails | |
Defined in Blockfrost.Types.Cardano.Addresses Methods parseJSON :: Value -> Parser AddressDetails # parseJSONList :: Value -> Parser [AddressDetails] # | |
FromJSON AddressInfo | |
Defined in Blockfrost.Types.Cardano.Addresses | |
FromJSON AddressInfoExtended | |
Defined in Blockfrost.Types.Cardano.Addresses Methods parseJSON :: Value -> Parser AddressInfoExtended # parseJSONList :: Value -> Parser [AddressInfoExtended] # | |
FromJSON AddressTransaction | |
Defined in Blockfrost.Types.Cardano.Addresses Methods parseJSON :: Value -> Parser AddressTransaction # parseJSONList :: Value -> Parser [AddressTransaction] # | |
FromJSON AddressType | |
Defined in Blockfrost.Types.Cardano.Addresses | |
FromJSON AddressUtxo | |
Defined in Blockfrost.Types.Cardano.Addresses | |
FromJSON AssetAction | |
Defined in Blockfrost.Types.Cardano.Assets | |
FromJSON AssetAddress | |
Defined in Blockfrost.Types.Cardano.Assets | |
FromJSON AssetDetails | |
Defined in Blockfrost.Types.Cardano.Assets | |
FromJSON AssetHistory | |
Defined in Blockfrost.Types.Cardano.Assets | |
FromJSON AssetInfo | |
Defined in Blockfrost.Types.Cardano.Assets | |
FromJSON AssetMetadata | |
Defined in Blockfrost.Types.Cardano.Assets Methods parseJSON :: Value -> Parser AssetMetadata # parseJSONList :: Value -> Parser [AssetMetadata] # | |
FromJSON AssetOnChainMetadata | |
Defined in Blockfrost.Types.Cardano.Assets Methods parseJSON :: Value -> Parser AssetOnChainMetadata # parseJSONList :: Value -> Parser [AssetOnChainMetadata] # | |
FromJSON AssetTransaction | |
Defined in Blockfrost.Types.Cardano.Assets Methods parseJSON :: Value -> Parser AssetTransaction # parseJSONList :: Value -> Parser [AssetTransaction] # | |
FromJSON MetadataMediaFile | |
Defined in Blockfrost.Types.Cardano.Assets Methods parseJSON :: Value -> Parser MetadataMediaFile # parseJSONList :: Value -> Parser [MetadataMediaFile] # | |
FromJSON Block | |
Defined in Blockfrost.Types.Cardano.Blocks | |
FromJSON TxHashCBOR | |
Defined in Blockfrost.Types.Cardano.Blocks | |
FromJSON CostModels | |
Defined in Blockfrost.Types.Cardano.Epochs | |
FromJSON CostModelsRaw | |
Defined in Blockfrost.Types.Cardano.Epochs Methods parseJSON :: Value -> Parser CostModelsRaw # parseJSONList :: Value -> Parser [CostModelsRaw] # | |
FromJSON EpochInfo | |
Defined in Blockfrost.Types.Cardano.Epochs | |
FromJSON PoolStakeDistribution | |
Defined in Blockfrost.Types.Cardano.Epochs Methods parseJSON :: Value -> Parser PoolStakeDistribution # parseJSONList :: Value -> Parser [PoolStakeDistribution] # | |
FromJSON ProtocolParams | |
Defined in Blockfrost.Types.Cardano.Epochs Methods parseJSON :: Value -> Parser ProtocolParams # parseJSONList :: Value -> Parser [ProtocolParams] # | |
FromJSON StakeDistribution | |
Defined in Blockfrost.Types.Cardano.Epochs Methods parseJSON :: Value -> Parser StakeDistribution # parseJSONList :: Value -> Parser [StakeDistribution] # | |
FromJSON Genesis | |
Defined in Blockfrost.Types.Cardano.Genesis | |
FromJSON MempoolRedeemer | |
Defined in Blockfrost.Types.Cardano.Mempool Methods parseJSON :: Value -> Parser MempoolRedeemer # parseJSONList :: Value -> Parser [MempoolRedeemer] # | |
FromJSON MempoolTransaction | |
Defined in Blockfrost.Types.Cardano.Mempool Methods parseJSON :: Value -> Parser MempoolTransaction # parseJSONList :: Value -> Parser [MempoolTransaction] # | |
FromJSON MempoolUTxOInput | |
Defined in Blockfrost.Types.Cardano.Mempool Methods parseJSON :: Value -> Parser MempoolUTxOInput # parseJSONList :: Value -> Parser [MempoolUTxOInput] # | |
FromJSON TransactionInMempool | |
Defined in Blockfrost.Types.Cardano.Mempool Methods parseJSON :: Value -> Parser TransactionInMempool # parseJSONList :: Value -> Parser [TransactionInMempool] # | |
FromJSON TxMeta | |
Defined in Blockfrost.Types.Cardano.Metadata | |
FromJSON TxMetaCBOR | |
Defined in Blockfrost.Types.Cardano.Metadata | |
FromJSON TxMetaJSON | |
Defined in Blockfrost.Types.Cardano.Metadata | |
FromJSON Network | |
Defined in Blockfrost.Types.Cardano.Network | |
FromJSON NetworkEraBound | |
Defined in Blockfrost.Types.Cardano.Network Methods parseJSON :: Value -> Parser NetworkEraBound # parseJSONList :: Value -> Parser [NetworkEraBound] # | |
FromJSON NetworkEraParameters | |
Defined in Blockfrost.Types.Cardano.Network Methods parseJSON :: Value -> Parser NetworkEraParameters # parseJSONList :: Value -> Parser [NetworkEraParameters] # | |
FromJSON NetworkEraSummary | |
Defined in Blockfrost.Types.Cardano.Network Methods parseJSON :: Value -> Parser NetworkEraSummary # parseJSONList :: Value -> Parser [NetworkEraSummary] # | |
FromJSON NetworkStake | |
Defined in Blockfrost.Types.Cardano.Network | |
FromJSON NetworkSupply | |
Defined in Blockfrost.Types.Cardano.Network Methods parseJSON :: Value -> Parser NetworkSupply # parseJSONList :: Value -> Parser [NetworkSupply] # | |
FromJSON Pool | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolDelegator | |
Defined in Blockfrost.Types.Cardano.Pools Methods parseJSON :: Value -> Parser PoolDelegator # parseJSONList :: Value -> Parser [PoolDelegator] # | |
FromJSON PoolEpoch | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolHistory | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolInfo | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolMetadata | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolMetadataResponse | |
Defined in Blockfrost.Types.Cardano.Pools Methods parseJSON :: Value -> Parser PoolMetadataResponse # parseJSONList :: Value -> Parser [PoolMetadataResponse] # | |
FromJSON PoolRegistrationAction | |
Defined in Blockfrost.Types.Cardano.Pools Methods parseJSON :: Value -> Parser PoolRegistrationAction # parseJSONList :: Value -> Parser [PoolRegistrationAction] # | |
FromJSON PoolRelay | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON PoolUpdate | |
Defined in Blockfrost.Types.Cardano.Pools | |
FromJSON InlineDatum | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON Script | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON ScriptCBOR | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON ScriptDatum | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON ScriptDatumCBOR | |
Defined in Blockfrost.Types.Cardano.Scripts Methods parseJSON :: Value -> Parser ScriptDatumCBOR # parseJSONList :: Value -> Parser [ScriptDatumCBOR] # | |
FromJSON ScriptJSON | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON ScriptRedeemer | |
Defined in Blockfrost.Types.Cardano.Scripts Methods parseJSON :: Value -> Parser ScriptRedeemer # parseJSONList :: Value -> Parser [ScriptRedeemer] # | |
FromJSON ScriptType | |
Defined in Blockfrost.Types.Cardano.Scripts | |
FromJSON PoolUpdateMetadata | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser PoolUpdateMetadata # parseJSONList :: Value -> Parser [PoolUpdateMetadata] # | |
FromJSON Pot | |
Defined in Blockfrost.Types.Cardano.Transactions | |
FromJSON Transaction | |
Defined in Blockfrost.Types.Cardano.Transactions | |
FromJSON TransactionCBOR | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionCBOR # parseJSONList :: Value -> Parser [TransactionCBOR] # | |
FromJSON TransactionDelegation | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionDelegation # parseJSONList :: Value -> Parser [TransactionDelegation] # | |
FromJSON TransactionMetaCBOR | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionMetaCBOR # parseJSONList :: Value -> Parser [TransactionMetaCBOR] # | |
FromJSON TransactionMetaJSON | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionMetaJSON # parseJSONList :: Value -> Parser [TransactionMetaJSON] # | |
FromJSON TransactionMir | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionMir # parseJSONList :: Value -> Parser [TransactionMir] # | |
FromJSON TransactionPoolRetiring | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionPoolRetiring # parseJSONList :: Value -> Parser [TransactionPoolRetiring] # | |
FromJSON TransactionPoolUpdate | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionPoolUpdate # parseJSONList :: Value -> Parser [TransactionPoolUpdate] # | |
FromJSON TransactionRedeemer | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionRedeemer # parseJSONList :: Value -> Parser [TransactionRedeemer] # | |
FromJSON TransactionStake | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionStake # parseJSONList :: Value -> Parser [TransactionStake] # | |
FromJSON TransactionUtxos | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionUtxos # parseJSONList :: Value -> Parser [TransactionUtxos] # | |
FromJSON TransactionWithdrawal | |
Defined in Blockfrost.Types.Cardano.Transactions Methods parseJSON :: Value -> Parser TransactionWithdrawal # parseJSONList :: Value -> Parser [TransactionWithdrawal] # | |
FromJSON UtxoInput | |
Defined in Blockfrost.Types.Cardano.Transactions | |
FromJSON UtxoOutput | |
Defined in Blockfrost.Types.Cardano.Transactions | |
FromJSON DerivedAddress | |
Defined in Blockfrost.Types.Cardano.Utils Methods parseJSON :: Value -> Parser DerivedAddress # parseJSONList :: Value -> Parser [DerivedAddress] # | |
FromJSON TxEval | |
Defined in Blockfrost.Types.Cardano.Utils | |
FromJSON TxEvalBudget | |
Defined in Blockfrost.Types.Cardano.Utils | |
FromJSON TxEvalFailure | |
Defined in Blockfrost.Types.Cardano.Utils | |
FromJSON TxEvalInput | |
Defined in Blockfrost.Types.Cardano.Utils | |
FromJSON TxEvalValidator | |
Defined in Blockfrost.Types.Cardano.Utils Methods parseJSON :: Value -> Parser TxEvalValidator # parseJSONList :: Value -> Parser [TxEvalValidator] # | |
FromJSON Healthy | |
Defined in Blockfrost.Types.Common | |
FromJSON Metric | |
Defined in Blockfrost.Types.Common | |
FromJSON ServerTime | |
Defined in Blockfrost.Types.Common | |
FromJSON URLVersion | |
Defined in Blockfrost.Types.Common | |
FromJSON IPFSAdd | |
Defined in Blockfrost.Types.IPFS | |
FromJSON IPFSPin | |
Defined in Blockfrost.Types.IPFS | |
FromJSON IPFSPinChange | |
Defined in Blockfrost.Types.IPFS Methods parseJSON :: Value -> Parser IPFSPinChange # parseJSONList :: Value -> Parser [IPFSPinChange] # | |
FromJSON PinState | |
Defined in Blockfrost.Types.IPFS | |
FromJSON NutlinkAddress | |
Defined in Blockfrost.Types.NutLink Methods parseJSON :: Value -> Parser NutlinkAddress # parseJSONList :: Value -> Parser [NutlinkAddress] # | |
FromJSON NutlinkAddressTicker | |
Defined in Blockfrost.Types.NutLink Methods parseJSON :: Value -> Parser NutlinkAddressTicker # parseJSONList :: Value -> Parser [NutlinkAddressTicker] # | |
FromJSON NutlinkTicker | |
Defined in Blockfrost.Types.NutLink Methods parseJSON :: Value -> Parser NutlinkTicker # parseJSONList :: Value -> Parser [NutlinkTicker] # | |
FromJSON Address | |
Defined in Blockfrost.Types.Shared.Address | |
FromJSON Amount | |
Defined in Blockfrost.Types.Shared.Amount | |
FromJSON AmountExtended | |
Defined in Blockfrost.Types.Shared.Amount Methods parseJSON :: Value -> Parser AmountExtended # parseJSONList :: Value -> Parser [AmountExtended] # | |
FromJSON AssetId | |
Defined in Blockfrost.Types.Shared.AssetId | |
FromJSON BlockHash | |
Defined in Blockfrost.Types.Shared.BlockHash | |
FromJSON CBORString | |
Defined in Blockfrost.Types.Shared.CBOR | |
FromJSON DatumHash | |
Defined in Blockfrost.Types.Shared.DatumHash | |
FromJSON Epoch | |
Defined in Blockfrost.Types.Shared.Epoch | |
FromJSON EpochLength | |
Defined in Blockfrost.Types.Shared.Epoch | |
FromJSON POSIXMillis | |
Defined in Blockfrost.Types.Shared.POSIXMillis | |
FromJSON PolicyId | |
Defined in Blockfrost.Types.Shared.PolicyId | |
FromJSON PoolId | |
Defined in Blockfrost.Types.Shared.PoolId | |
FromJSON Quantity | |
Defined in Blockfrost.Types.Shared.Quantity | |
FromJSON ScriptHash | |
Defined in Blockfrost.Types.Shared.ScriptHash | |
FromJSON ScriptHashList | |
Defined in Blockfrost.Types.Shared.ScriptHash Methods parseJSON :: Value -> Parser ScriptHashList # parseJSONList :: Value -> Parser [ScriptHashList] # | |
FromJSON Slot | |
Defined in Blockfrost.Types.Shared.Slot | |
FromJSON TxHash | |
Defined in Blockfrost.Types.Shared.TxHash | |
FromJSON TxHashObject | |
Defined in Blockfrost.Types.Shared.TxHash | |
FromJSON ValidationPurpose | |
Defined in Blockfrost.Types.Shared.ValidationPurpose Methods parseJSON :: Value -> Parser ValidationPurpose # parseJSONList :: Value -> Parser [ValidationPurpose] # | |
(TypeError ('Text "Forbidden FromJSON ByteString instance") :: Constraint) => FromJSON ByteString # | |
Defined in GeniusYield.Imports | |
FromJSON Cosigner | |
Defined in Cardano.Address.Script | |
FromJSON ScriptTemplate | |
Defined in Cardano.Address.Script Methods parseJSON :: Value -> Parser ScriptTemplate # parseJSONList :: Value -> Parser [ScriptTemplate] # | |
FromJSON StakeAddress | |
Defined in Cardano.Api.Internal.Address | |
FromJSON ChainPoint | |
Defined in Cardano.Api.Internal.Block | |
FromJSON AnyShelleyBasedEra | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods parseJSON :: Value -> Parser AnyShelleyBasedEra # parseJSONList :: Value -> Parser [AnyShelleyBasedEra] # | |
FromJSON AnyCardanoEra | |
Defined in Cardano.Api.Internal.Eras.Core Methods parseJSON :: Value -> Parser AnyCardanoEra # parseJSONList :: Value -> Parser [AnyCardanoEra] # | |
FromJSON DoNotList | |
FromJSON ImageObject | |
FromJSON Reference | |
FromJSON ReferenceType | |
FromJSON Author | |
FromJSON Reference | |
FromJSON ReferenceHash | |
FromJSON ReferenceType | |
FromJSON Witness | |
FromJSON WitnessAlgorithm | |
FromJSON NodeConfig | |
Defined in Cardano.Api.Internal.LedgerState | |
FromJSON CostModels | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromJSON ExecutionUnitPrices | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods parseJSON :: Value -> Parser ExecutionUnitPrices # parseJSONList :: Value -> Parser [ExecutionUnitPrices] # | |
FromJSON PraosNonce | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromJSON ProtocolParameters | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromJSON AnyPlutusScriptVersion | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser AnyPlutusScriptVersion # parseJSONList :: Value -> Parser [AnyPlutusScriptVersion] # | |
FromJSON ExecutionUnits | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser ExecutionUnits # parseJSONList :: Value -> Parser [ExecutionUnits] # | |
FromJSON ScriptHash | |
Defined in Cardano.Api.Internal.Script | |
FromJSON ScriptInAnyLang | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser ScriptInAnyLang # parseJSONList :: Value -> Parser [ScriptInAnyLang] # | |
FromJSON SimpleScript | |
Defined in Cardano.Api.Internal.Script | |
FromJSON TextEnvelope | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope | |
FromJSON TextEnvelopeDescr | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods parseJSON :: Value -> Parser TextEnvelopeDescr # parseJSONList :: Value -> Parser [TextEnvelopeDescr] # | |
FromJSON TextEnvelopeType | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods parseJSON :: Value -> Parser TextEnvelopeType # parseJSONList :: Value -> Parser [TextEnvelopeType] # | |
FromJSON StakePoolMetadata | |
Defined in Cardano.Api.Internal.StakePoolMetadata Methods parseJSON :: Value -> Parser StakePoolMetadata # parseJSONList :: Value -> Parser [StakePoolMetadata] # | |
FromJSON TxId | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSON TxIn | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSON TxIx | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSON AssetName | |
Defined in Cardano.Api.Internal.Value | |
FromJSON PolicyId | |
Defined in Cardano.Api.Internal.Value | |
FromJSON Quantity | |
Defined in Cardano.Api.Internal.Value | |
FromJSON Value | |
Defined in Cardano.Api.Internal.Value | |
FromJSON ValueNestedRep | |
Defined in Cardano.Api.Internal.Value Methods parseJSON :: Value -> Parser ValueNestedRep # parseJSONList :: Value -> Parser [ValueNestedRep] # | |
FromJSON ProtocolMagic | |
Defined in Cardano.Crypto.ProtocolMagic Methods parseJSON :: Value -> Parser ProtocolMagic # parseJSONList :: Value -> Parser [ProtocolMagic] # | |
FromJSON ProtocolMagicId | |
Defined in Cardano.Crypto.ProtocolMagic Methods parseJSON :: Value -> Parser ProtocolMagicId # parseJSONList :: Value -> Parser [ProtocolMagicId] # | |
FromJSON RequiresNetworkMagic | |
Defined in Cardano.Crypto.ProtocolMagic Methods parseJSON :: Value -> Parser RequiresNetworkMagic # parseJSONList :: Value -> Parser [RequiresNetworkMagic] # | |
FromJSON CompactRedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.Compact | |
FromJSON RedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.VerificationKey Methods parseJSON :: Value -> Parser RedeemVerificationKey # parseJSONList :: Value -> Parser [RedeemVerificationKey] # | |
FromJSON VerificationKey | |
Defined in Cardano.Crypto.Signing.VerificationKey Methods parseJSON :: Value -> Parser VerificationKey # parseJSONList :: Value -> Parser [VerificationKey] # | |
FromJSON AlonzoGenesis | |
Defined in Cardano.Ledger.Alonzo.Genesis Methods parseJSON :: Value -> Parser AlonzoGenesis # parseJSONList :: Value -> Parser [AlonzoGenesis] # | |
FromJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams | |
FromJSON OrdExUnits | |
Defined in Cardano.Ledger.Alonzo.PParams | |
FromJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams | |
FromJSON Version | |
Defined in Cardano.Ledger.Binary.Version | |
FromJSON ConwayGenesis | |
Defined in Cardano.Ledger.Conway.Genesis Methods parseJSON :: Value -> Parser ConwayGenesis # parseJSONList :: Value -> Parser [ConwayGenesis] # | |
FromJSON DRepVotingThresholds | |
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser DRepVotingThresholds # parseJSONList :: Value -> Parser [DRepVotingThresholds] # | |
FromJSON PoolVotingThresholds | |
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser PoolVotingThresholds # parseJSONList :: Value -> Parser [PoolVotingThresholds] # | |
FromJSON Delegatee | |
Defined in Cardano.Ledger.Conway.TxCert | |
FromJSON Addr | |
Defined in Cardano.Ledger.Address | |
FromJSON RewardAccount | |
Defined in Cardano.Ledger.Address Methods parseJSON :: Value -> Parser RewardAccount # parseJSONList :: Value -> Parser [RewardAccount] # | |
FromJSON Anchor | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON BlocksMade | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON Network | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON NonNegativeInterval | |
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser NonNegativeInterval # parseJSONList :: Value -> Parser [NonNegativeInterval] # | |
FromJSON Nonce | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON Port | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON PositiveInterval | |
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser PositiveInterval # parseJSONList :: Value -> Parser [PositiveInterval] # | |
FromJSON PositiveUnitInterval | |
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser PositiveUnitInterval # parseJSONList :: Value -> Parser [PositiveUnitInterval] # | |
FromJSON ProtVer | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON Relation | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON UnitInterval | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON Url | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON Coin | |
Defined in Cardano.Ledger.Coin | |
FromJSON DeltaCoin | |
Defined in Cardano.Ledger.Coin | |
FromJSON SlotNo32 | |
Defined in Cardano.Ledger.Credential | |
FromJSON DRep | |
Defined in Cardano.Ledger.DRep | |
FromJSON DRepState | |
Defined in Cardano.Ledger.DRep | |
FromJSON GenDelegPair | |
Defined in Cardano.Ledger.Hashes | |
FromJSON GenDelegs | |
Defined in Cardano.Ledger.Hashes | |
FromJSON ScriptHash | |
Defined in Cardano.Ledger.Hashes | |
FromJSON CostModels | |
Defined in Cardano.Ledger.Plutus.CostModels | |
FromJSON ExUnits | |
Defined in Cardano.Ledger.Plutus.ExUnits | |
FromJSON Prices | |
Defined in Cardano.Ledger.Plutus.ExUnits | |
FromJSON Language | |
Defined in Cardano.Ledger.Plutus.Language | |
FromJSON PoolMetadata | |
Defined in Cardano.Ledger.PoolParams | |
FromJSON PoolParams | |
Defined in Cardano.Ledger.PoolParams | |
FromJSON StakePoolRelay | |
Defined in Cardano.Ledger.PoolParams Methods parseJSON :: Value -> Parser StakePoolRelay # parseJSONList :: Value -> Parser [StakePoolRelay] # | |
FromJSON TxId | |
Defined in Cardano.Ledger.TxIn | |
FromJSON PolicyID | |
Defined in Cardano.Ledger.Mary.Value | |
FromJSON RewardInfoPool | |
Defined in Cardano.Ledger.Shelley.API.Wallet Methods parseJSON :: Value -> Parser RewardInfoPool # parseJSONList :: Value -> Parser [RewardInfoPool] # | |
FromJSON RewardParams | |
Defined in Cardano.Ledger.Shelley.API.Wallet | |
FromJSON LegacyJSONPParams | |
Defined in Cardano.Ledger.Shelley.Genesis | |
FromJSON NominalDiffTimeMicro | |
Defined in Cardano.Ledger.Shelley.Genesis Methods parseJSON :: Value -> Parser NominalDiffTimeMicro # parseJSONList :: Value -> Parser [NominalDiffTimeMicro] # | |
FromJSON ShelleyGenesis | |
Defined in Cardano.Ledger.Shelley.Genesis Methods parseJSON :: Value -> Parser ShelleyGenesis # parseJSONList :: Value -> Parser [ShelleyGenesis] # | |
FromJSON ShelleyGenesisStaking | |
Defined in Cardano.Ledger.Shelley.Genesis Methods parseJSON :: Value -> Parser ShelleyGenesisStaking # parseJSONList :: Value -> Parser [ShelleyGenesisStaking] # | |
FromJSON LogWeight | |
Defined in Cardano.Ledger.Shelley.PoolRank | |
FromJSON Desirability | |
Defined in Cardano.Ledger.Shelley.RewardProvenance | |
FromJSON RewardProvenance | |
Defined in Cardano.Ledger.Shelley.RewardProvenance Methods parseJSON :: Value -> Parser RewardProvenance # parseJSONList :: Value -> Parser [RewardProvenance] # | |
FromJSON RewardProvenancePool | |
Defined in Cardano.Ledger.Shelley.RewardProvenance Methods parseJSON :: Value -> Parser RewardProvenancePool # parseJSONList :: Value -> Parser [RewardProvenancePool] # | |
FromJSON NCForkPolicy | |
Defined in Cardano.Node.Configuration.POM | |
FromJSON PartialNodeConfiguration | |
Defined in Cardano.Node.Configuration.POM Methods parseJSON :: Value -> Parser PartialNodeConfiguration # parseJSONList :: Value -> Parser [PartialNodeConfiguration] # | |
FromJSON ShutdownOn | |
Defined in Cardano.Node.Handlers.Shutdown | |
FromJSON ShutdownTrace | |
Defined in Cardano.Node.Handlers.Shutdown Methods parseJSON :: Value -> Parser ShutdownTrace # parseJSONList :: Value -> Parser [ShutdownTrace] # | |
FromJSON Protocol | |
Defined in Cardano.Node.Protocol.Types | |
FromJSON NodeInfo | |
Defined in Cardano.Node.Startup | |
FromJSON NodeStartupInfo | |
Defined in Cardano.Node.Startup Methods parseJSON :: Value -> Parser NodeStartupInfo # parseJSONList :: Value -> Parser [NodeStartupInfo] # | |
FromJSON CheckpointsFile | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser CheckpointsFile # parseJSONList :: Value -> Parser [CheckpointsFile] # | |
FromJSON CheckpointsHash | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser CheckpointsHash # parseJSONList :: Value -> Parser [CheckpointsHash] # | |
FromJSON GenesisFile | |
Defined in Cardano.Node.Types | |
FromJSON GenesisHash | |
Defined in Cardano.Node.Types | |
FromJSON MaxConcurrencyBulkSync | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser MaxConcurrencyBulkSync # parseJSONList :: Value -> Parser [MaxConcurrencyBulkSync] # | |
FromJSON MaxConcurrencyDeadline | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser MaxConcurrencyDeadline # parseJSONList :: Value -> Parser [MaxConcurrencyDeadline] # | |
FromJSON NodeConsensusMode | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser NodeConsensusMode # parseJSONList :: Value -> Parser [NodeConsensusMode] # | |
FromJSON NodeDiffusionMode | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser NodeDiffusionMode # parseJSONList :: Value -> Parser [NodeDiffusionMode] # | |
FromJSON PeerSnapshotFile | |
Defined in Cardano.Node.Types Methods parseJSON :: Value -> Parser PeerSnapshotFile # parseJSONList :: Value -> Parser [PeerSnapshotFile] # | |
FromJSON PartialTraceSelection | |
Defined in Cardano.Tracing.Config Methods parseJSON :: Value -> Parser PartialTraceSelection # parseJSONList :: Value -> Parser [PartialTraceSelection] # | |
FromJSON BlockNo | |
Defined in Cardano.Slotting.Block | |
FromJSON EpochInterval | |
Defined in Cardano.Slotting.Slot Methods parseJSON :: Value -> Parser EpochInterval # parseJSONList :: Value -> Parser [EpochInterval] # | |
FromJSON EpochNo | |
Defined in Cardano.Slotting.Slot | |
FromJSON EpochSize | |
Defined in Cardano.Slotting.Slot | |
FromJSON SlotNo | |
Defined in Cardano.Slotting.Slot | |
FromJSON RelativeTime | |
Defined in Cardano.Slotting.Time | |
FromJSON SystemStart | |
Defined in Cardano.Slotting.Time | |
FromJSON Kind | |
Defined in Testnet.Property.Assert | |
FromJSON TraceNode | |
Defined in Testnet.Property.Assert | |
FromJSON LeadershipSlot | |
Defined in Testnet.Types Methods parseJSON :: Value -> Parser LeadershipSlot # parseJSONList :: Value -> Parser [LeadershipSlot] # | |
FromJSON IntSet | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Void | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON All | Since: aeson-2.2.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Any | Since: aeson-2.2.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Version | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON CTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Int16 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Int32 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Int64 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Int8 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Word16 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Word32 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Word64 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Word8 | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Ordering | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Component | |
Defined in Hedgehog.Extras.Internal.Plan | |
FromJSON Plan | |
Defined in Hedgehog.Extras.Internal.Plan | |
FromJSON Aggregated | |
Defined in Cardano.BM.Data.Aggregated | |
FromJSON BaseStats | |
Defined in Cardano.BM.Data.Aggregated | |
FromJSON EWMA | |
Defined in Cardano.BM.Data.Aggregated | |
FromJSON Measurable | |
Defined in Cardano.BM.Data.Aggregated | |
FromJSON Stats | |
Defined in Cardano.BM.Data.Aggregated | |
FromJSON AggregatedKind | |
Defined in Cardano.BM.Data.AggregatedKind Methods parseJSON :: Value -> Parser AggregatedKind # parseJSONList :: Value -> Parser [AggregatedKind] # | |
FromJSON BackendKind | |
Defined in Cardano.BM.Data.BackendKind | |
FromJSON Endpoint | |
Defined in Cardano.BM.Data.Configuration | |
FromJSON RemoteAddr | |
Defined in Cardano.BM.Data.Configuration | |
FromJSON RemoteAddrNamed | |
Defined in Cardano.BM.Data.Configuration Methods parseJSON :: Value -> Parser RemoteAddrNamed # parseJSONList :: Value -> Parser [RemoteAddrNamed] # | |
FromJSON Representation | |
Defined in Cardano.BM.Data.Configuration Methods parseJSON :: Value -> Parser Representation # parseJSONList :: Value -> Parser [Representation] # | |
FromJSON Counter | |
Defined in Cardano.BM.Data.Counter | |
FromJSON CounterState | |
Defined in Cardano.BM.Data.Counter | |
FromJSON CounterType | |
Defined in Cardano.BM.Data.Counter | |
FromJSON CommandValue | |
Defined in Cardano.BM.Data.LogItem | |
FromJSON LOMeta | |
Defined in Cardano.BM.Data.LogItem | |
FromJSON MonitorAction | |
Defined in Cardano.BM.Data.LogItem Methods parseJSON :: Value -> Parser MonitorAction # parseJSONList :: Value -> Parser [MonitorAction] # | |
FromJSON PrivacyAnnotation | |
Defined in Cardano.BM.Data.LogItem Methods parseJSON :: Value -> Parser PrivacyAnnotation # parseJSONList :: Value -> Parser [PrivacyAnnotation] # | |
FromJSON ObservableInstance | |
Defined in Cardano.BM.Data.Observable Methods parseJSON :: Value -> Parser ObservableInstance # parseJSONList :: Value -> Parser [ObservableInstance] # | |
FromJSON ScribeDefinition | |
Defined in Cardano.BM.Data.Output Methods parseJSON :: Value -> Parser ScribeDefinition # parseJSONList :: Value -> Parser [ScribeDefinition] # | |
FromJSON ScribeFormat | |
Defined in Cardano.BM.Data.Output | |
FromJSON ScribeKind | |
Defined in Cardano.BM.Data.Output | |
FromJSON ScribePrivacy | |
Defined in Cardano.BM.Data.Output Methods parseJSON :: Value -> Parser ScribePrivacy # parseJSONList :: Value -> Parser [ScribePrivacy] # | |
FromJSON RotationParameters | |
Defined in Cardano.BM.Data.Rotation Methods parseJSON :: Value -> Parser RotationParameters # parseJSONList :: Value -> Parser [RotationParameters] # | |
FromJSON Severity | |
Defined in Cardano.BM.Data.Severity | |
FromJSON DropName | |
Defined in Cardano.BM.Data.SubTrace | |
FromJSON NameSelector | |
Defined in Cardano.BM.Data.SubTrace | |
FromJSON SubTrace | |
Defined in Cardano.BM.Data.SubTrace | |
FromJSON UnhideNames | |
Defined in Cardano.BM.Data.SubTrace | |
FromJSON TracingVerbosity | |
Defined in Cardano.BM.Data.Tracer Methods parseJSON :: Value -> Parser TracingVerbosity # parseJSONList :: Value -> Parser [TracingVerbosity] # | |
FromJSON Environment | |
Defined in Katip.Core | |
FromJSON LocJs | |
Defined in Katip.Core | |
FromJSON LogStr | |
Defined in Katip.Core | |
FromJSON Namespace | |
Defined in Katip.Core | |
FromJSON ProcessIDJs | |
Defined in Katip.Core | |
FromJSON Severity | |
Defined in Katip.Core | |
FromJSON ThreadIdText | |
Defined in Katip.Core | |
FromJSON Verbosity | |
Defined in Katip.Core | |
FromJSON ApiError | |
Defined in Maestro.Client.Error | |
FromJSON AbsoluteSlot | |
Defined in Maestro.Types.Common | |
FromJSON BlockHash | |
Defined in Maestro.Types.Common | |
FromJSON BlockHeight | |
Defined in Maestro.Types.Common | |
FromJSON DatumOption | |
Defined in Maestro.Types.Common | |
FromJSON DatumOptionType | |
Defined in Maestro.Types.Common Methods parseJSON :: Value -> Parser DatumOptionType # parseJSONList :: Value -> Parser [DatumOptionType] # | |
FromJSON EpochNo | |
Defined in Maestro.Types.Common | |
FromJSON EpochSize | |
Defined in Maestro.Types.Common | |
FromJSON PolicyId | |
Defined in Maestro.Types.Common | |
FromJSON Script | |
Defined in Maestro.Types.Common | |
FromJSON ScriptType | |
Defined in Maestro.Types.Common | |
FromJSON SlotNo | |
Defined in Maestro.Types.Common | |
FromJSON TokenName | |
Defined in Maestro.Types.Common | |
FromJSON TxHash | |
Defined in Maestro.Types.Common | |
FromJSON TxIndex | |
Defined in Maestro.Types.Common | |
FromJSON AccountAction | |
Defined in Maestro.Types.V1.Accounts | |
FromJSON AccountHistory | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser AccountHistory # parseJSONList :: Value -> Parser [AccountHistory] # | |
FromJSON AccountInfo | |
Defined in Maestro.Types.V1.Accounts | |
FromJSON AccountReward | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser AccountReward # parseJSONList :: Value -> Parser [AccountReward] # | |
FromJSON AccountStakingRewardType | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser AccountStakingRewardType # parseJSONList :: Value -> Parser [AccountStakingRewardType] # | |
FromJSON AccountUpdate | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser AccountUpdate # parseJSONList :: Value -> Parser [AccountUpdate] # | |
FromJSON PaginatedAccountHistory | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser PaginatedAccountHistory # parseJSONList :: Value -> Parser [PaginatedAccountHistory] # | |
FromJSON PaginatedAccountReward | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser PaginatedAccountReward # parseJSONList :: Value -> Parser [PaginatedAccountReward] # | |
FromJSON PaginatedAccountUpdate | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser PaginatedAccountUpdate # parseJSONList :: Value -> Parser [PaginatedAccountUpdate] # | |
FromJSON PaginatedAddress | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser PaginatedAddress # parseJSONList :: Value -> Parser [PaginatedAddress] # | |
FromJSON PaginatedAsset | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser PaginatedAsset # parseJSONList :: Value -> Parser [PaginatedAsset] # | |
FromJSON TimestampedAccountInfo | |
Defined in Maestro.Types.V1.Accounts Methods parseJSON :: Value -> Parser TimestampedAccountInfo # parseJSONList :: Value -> Parser [TimestampedAccountInfo] # | |
FromJSON AddressInfo | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON AddressTransaction | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser AddressTransaction # parseJSONList :: Value -> Parser [AddressTransaction] # | |
FromJSON CertIndex | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON ChainPointer | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON NetworkId | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON OutputReferenceObject | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser OutputReferenceObject # parseJSONList :: Value -> Parser [OutputReferenceObject] # | |
FromJSON PaginatedAddressTransaction | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON PaginatedOutputReferenceObject | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON PaginatedPaymentCredentialTransaction | |
FromJSON PaymentCredKind | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser PaymentCredKind # parseJSONList :: Value -> Parser [PaymentCredKind] # | |
FromJSON PaymentCredential | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser PaymentCredential # parseJSONList :: Value -> Parser [PaymentCredential] # | |
FromJSON PaymentCredentialTransaction | |
Defined in Maestro.Types.V1.Addresses | |
FromJSON StakingCredKind | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser StakingCredKind # parseJSONList :: Value -> Parser [StakingCredKind] # | |
FromJSON StakingCredential | |
Defined in Maestro.Types.V1.Addresses Methods parseJSON :: Value -> Parser StakingCredential # parseJSONList :: Value -> Parser [StakingCredential] # | |
FromJSON AssetInfo | |
Defined in Maestro.Types.V1.Assets | |
FromJSON AssetStandards | |
Defined in Maestro.Types.V1.Assets | |
FromJSON AssetUTxOs | |
Defined in Maestro.Types.V1.Assets | |
FromJSON Cip68AssetType | |
Defined in Maestro.Types.V1.Assets | |
FromJSON Cip68Metadata | |
Defined in Maestro.Types.V1.Assets | |
FromJSON TimestampedAssetInfo | |
Defined in Maestro.Types.V1.Assets Methods parseJSON :: Value -> Parser TimestampedAssetInfo # parseJSONList :: Value -> Parser [TimestampedAssetInfo] # | |
FromJSON TimestampedAssetUTxOs | |
Defined in Maestro.Types.V1.Assets Methods parseJSON :: Value -> Parser TimestampedAssetUTxOs # parseJSONList :: Value -> Parser [TimestampedAssetUTxOs] # | |
FromJSON TokenRegistryMetadata | |
Defined in Maestro.Types.V1.Assets Methods parseJSON :: Value -> Parser TokenRegistryMetadata # parseJSONList :: Value -> Parser [TokenRegistryMetadata] # | |
FromJSON BlockDetails | |
Defined in Maestro.Types.V1.Blocks | |
FromJSON TimestampedBlockDetails | |
Defined in Maestro.Types.V1.Blocks Methods parseJSON :: Value -> Parser TimestampedBlockDetails # parseJSONList :: Value -> Parser [TimestampedBlockDetails] # | |
FromJSON Asset | |
Defined in Maestro.Types.V1.Common | |
FromJSON AssetUnit | |
Defined in Maestro.Types.V1.Common | |
FromJSON PaginatedUtxoWithSlot | |
Defined in Maestro.Types.V1.Common Methods parseJSON :: Value -> Parser PaginatedUtxoWithSlot # parseJSONList :: Value -> Parser [PaginatedUtxoWithSlot] # | |
FromJSON UtxoWithSlot | |
Defined in Maestro.Types.V1.Common | |
FromJSON NextCursor | |
Defined in Maestro.Types.V1.Common.Pagination | |
FromJSON LastUpdated | |
Defined in Maestro.Types.V1.Common.Timestamped | |
FromJSON Datum | |
Defined in Maestro.Types.V1.Datum | |
FromJSON TimestampedDatum | |
Defined in Maestro.Types.V1.Datum Methods parseJSON :: Value -> Parser TimestampedDatum # parseJSONList :: Value -> Parser [TimestampedDatum] # | |
FromJSON Dex | |
Defined in Maestro.Types.V1.DefiMarkets | |
FromJSON DexPairInfo | |
Defined in Maestro.Types.V1.DefiMarkets | |
FromJSON DexPairResponse | |
Defined in Maestro.Types.V1.DefiMarkets Methods parseJSON :: Value -> Parser DexPairResponse # parseJSONList :: Value -> Parser [DexPairResponse] # | |
FromJSON OHLCCandleInfo | |
Defined in Maestro.Types.V1.DefiMarkets Methods parseJSON :: Value -> Parser OHLCCandleInfo # parseJSONList :: Value -> Parser [OHLCCandleInfo] # | |
FromJSON Resolution | |
Defined in Maestro.Types.V1.DefiMarkets | |
FromJSON AsAda | |
Defined in Maestro.Types.V1.General | |
FromJSON AsBytes | |
Defined in Maestro.Types.V1.General | |
FromJSON AsLovelace | |
Defined in Maestro.Types.V1.General | |
FromJSON ChainTip | |
Defined in Maestro.Types.V1.General | |
FromJSON ConstitutionalCommittee | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser ConstitutionalCommittee # parseJSONList :: Value -> Parser [ConstitutionalCommittee] # | |
FromJSON CostModel | |
Defined in Maestro.Types.V1.General | |
FromJSON CostModels | |
Defined in Maestro.Types.V1.General | |
FromJSON DRepVotingThresholds | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser DRepVotingThresholds # parseJSONList :: Value -> Parser [DRepVotingThresholds] # | |
FromJSON EpochSlotLength | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser EpochSlotLength # parseJSONList :: Value -> Parser [EpochSlotLength] # | |
FromJSON EraBound | |
Defined in Maestro.Types.V1.General | |
FromJSON EraBoundTime | |
Defined in Maestro.Types.V1.General | |
FromJSON EraParameters | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser EraParameters # parseJSONList :: Value -> Parser [EraParameters] # | |
FromJSON EraSummary | |
Defined in Maestro.Types.V1.General | |
FromJSON MaestroRational | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser MaestroRational # parseJSONList :: Value -> Parser [MaestroRational] # | |
FromJSON MinFeeReferenceScripts | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser MinFeeReferenceScripts # parseJSONList :: Value -> Parser [MinFeeReferenceScripts] # | |
FromJSON ProtocolParameters | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser ProtocolParameters # parseJSONList :: Value -> Parser [ProtocolParameters] # | |
FromJSON ProtocolParametersUpdateDRep | |
Defined in Maestro.Types.V1.General | |
FromJSON ProtocolParametersUpdateStakePool | |
Defined in Maestro.Types.V1.General | |
FromJSON ProtocolVersion | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser ProtocolVersion # parseJSONList :: Value -> Parser [ProtocolVersion] # | |
FromJSON StakePoolVotingThresholds | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser StakePoolVotingThresholds # parseJSONList :: Value -> Parser [StakePoolVotingThresholds] # | |
FromJSON TimestampedChainTip | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser TimestampedChainTip # parseJSONList :: Value -> Parser [TimestampedChainTip] # | |
FromJSON TimestampedEraSummaries | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser TimestampedEraSummaries # parseJSONList :: Value -> Parser [TimestampedEraSummaries] # | |
FromJSON TimestampedProtocolParameters | |
Defined in Maestro.Types.V1.General | |
FromJSON TimestampedSystemStart | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser TimestampedSystemStart # parseJSONList :: Value -> Parser [TimestampedSystemStart] # | |
FromJSON PaginatedPoolListInfo | |
Defined in Maestro.Types.V1.Pools Methods parseJSON :: Value -> Parser PaginatedPoolListInfo # parseJSONList :: Value -> Parser [PaginatedPoolListInfo] # | |
FromJSON PoolListInfo | |
Defined in Maestro.Types.V1.Pools | |
FromJSON PaginatedUtxo | |
Defined in Maestro.Types.V1.Transactions Methods parseJSON :: Value -> Parser PaginatedUtxo # parseJSONList :: Value -> Parser [PaginatedUtxo] # | |
FromJSON TimestampedTxDetails | |
Defined in Maestro.Types.V1.Transactions Methods parseJSON :: Value -> Parser TimestampedTxDetails # parseJSONList :: Value -> Parser [TimestampedTxDetails] # | |
FromJSON TxDetails | |
Defined in Maestro.Types.V1.Transactions | |
FromJSON UtxoWithBytes | |
Defined in Maestro.Types.V1.Transactions Methods parseJSON :: Value -> Parser UtxoWithBytes # parseJSONList :: Value -> Parser [UtxoWithBytes] # | |
FromJSON URI | Since: aeson-2.2.0.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON AdditionalProperties | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser AdditionalProperties # parseJSONList :: Value -> Parser [AdditionalProperties] # | |
FromJSON ApiKeyLocation | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser ApiKeyLocation # parseJSONList :: Value -> Parser [ApiKeyLocation] # | |
FromJSON ApiKeyParams | |
Defined in Data.OpenApi.Internal | |
FromJSON Callback | |
Defined in Data.OpenApi.Internal | |
FromJSON Components | |
Defined in Data.OpenApi.Internal | |
FromJSON Contact | |
Defined in Data.OpenApi.Internal | |
FromJSON Discriminator | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser Discriminator # parseJSONList :: Value -> Parser [Discriminator] # | |
FromJSON Encoding | |
Defined in Data.OpenApi.Internal | |
FromJSON Example | |
Defined in Data.OpenApi.Internal | |
FromJSON ExpressionOrValue | All strings are parsed as expressions |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser ExpressionOrValue # parseJSONList :: Value -> Parser [ExpressionOrValue] # | |
FromJSON ExternalDocs | |
Defined in Data.OpenApi.Internal | |
FromJSON Header | |
Defined in Data.OpenApi.Internal | |
FromJSON Info | |
Defined in Data.OpenApi.Internal | |
FromJSON License | |
Defined in Data.OpenApi.Internal | |
FromJSON Link | |
Defined in Data.OpenApi.Internal | |
FromJSON MediaTypeObject | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser MediaTypeObject # parseJSONList :: Value -> Parser [MediaTypeObject] # | |
FromJSON MimeList | |
Defined in Data.OpenApi.Internal | |
FromJSON OAuth2AuthorizationCodeFlow | |
Defined in Data.OpenApi.Internal | |
FromJSON OAuth2ClientCredentialsFlow | |
Defined in Data.OpenApi.Internal | |
FromJSON OAuth2Flows | |
Defined in Data.OpenApi.Internal | |
FromJSON OAuth2ImplicitFlow | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser OAuth2ImplicitFlow # parseJSONList :: Value -> Parser [OAuth2ImplicitFlow] # | |
FromJSON OAuth2PasswordFlow | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser OAuth2PasswordFlow # parseJSONList :: Value -> Parser [OAuth2PasswordFlow] # | |
FromJSON OpenApi | |
Defined in Data.OpenApi.Internal | |
FromJSON OpenApiItems | |
Defined in Data.OpenApi.Internal | |
FromJSON OpenApiSpecVersion | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser OpenApiSpecVersion # parseJSONList :: Value -> Parser [OpenApiSpecVersion] # | |
FromJSON OpenApiType | |
Defined in Data.OpenApi.Internal | |
FromJSON Operation | |
Defined in Data.OpenApi.Internal | |
FromJSON Param | |
Defined in Data.OpenApi.Internal | |
FromJSON ParamLocation | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser ParamLocation # parseJSONList :: Value -> Parser [ParamLocation] # | |
FromJSON PathItem | |
Defined in Data.OpenApi.Internal | |
FromJSON Reference | |
Defined in Data.OpenApi.Internal | |
FromJSON RequestBody | |
Defined in Data.OpenApi.Internal | |
FromJSON Response | |
Defined in Data.OpenApi.Internal | |
FromJSON Responses | |
Defined in Data.OpenApi.Internal | |
FromJSON Schema | |
Defined in Data.OpenApi.Internal | |
FromJSON SecurityDefinitions | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser SecurityDefinitions # parseJSONList :: Value -> Parser [SecurityDefinitions] # | |
FromJSON SecurityRequirement | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser SecurityRequirement # parseJSONList :: Value -> Parser [SecurityRequirement] # | |
FromJSON SecurityScheme | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser SecurityScheme # parseJSONList :: Value -> Parser [SecurityScheme] # | |
FromJSON SecuritySchemeType | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser SecuritySchemeType # parseJSONList :: Value -> Parser [SecuritySchemeType] # | |
FromJSON Server | |
Defined in Data.OpenApi.Internal | |
FromJSON ServerVariable | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser ServerVariable # parseJSONList :: Value -> Parser [ServerVariable] # | |
FromJSON Style | |
Defined in Data.OpenApi.Internal | |
FromJSON Tag | |
Defined in Data.OpenApi.Internal | |
FromJSON URL | |
Defined in Data.OpenApi.Internal | |
FromJSON Xml | |
Defined in Data.OpenApi.Internal | |
FromJSON ConsensusMode | |
Defined in Cardano.Network.ConsensusMode Methods parseJSON :: Value -> Parser ConsensusMode # parseJSONList :: Value -> Parser [ConsensusMode] # | |
FromJSON NumberOfBigLedgerPeers | |
Defined in Cardano.Network.Types Methods parseJSON :: Value -> Parser NumberOfBigLedgerPeers # parseJSONList :: Value -> Parser [NumberOfBigLedgerPeers] # | |
FromJSON AccPoolStakeCoded | |
FromJSON LedgerPeerSnapshot | |
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Methods parseJSON :: Value -> Parser LedgerPeerSnapshot # parseJSONList :: Value -> Parser [LedgerPeerSnapshot] # | |
FromJSON PoolStakeCoded | |
FromJSON PeerAdvertise | |
Defined in Ouroboros.Network.PeerSelection.PeerAdvertise Methods parseJSON :: Value -> Parser PeerAdvertise # parseJSONList :: Value -> Parser [PeerAdvertise] # | |
FromJSON DomainAccessPoint | |
Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint Methods parseJSON :: Value -> Parser DomainAccessPoint # parseJSONList :: Value -> Parser [DomainAccessPoint] # | |
FromJSON RelayAccessPoint | |
Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint Methods parseJSON :: Value -> Parser RelayAccessPoint # parseJSONList :: Value -> Parser [RelayAccessPoint] # | |
FromJSON CpuAndMemoryModel | |
Defined in PlutusCore.Evaluation.Machine.CostingFun.SimpleJSON Methods parseJSON :: Value -> Parser CpuAndMemoryModel # parseJSONList :: Value -> Parser [CpuAndMemoryModel] # | |
FromJSON LinearFunction | |
Defined in PlutusCore.Evaluation.Machine.CostingFun.SimpleJSON Methods parseJSON :: Value -> Parser LinearFunction # parseJSONList :: Value -> Parser [LinearFunction] # | |
FromJSON Model | |
FromJSON OneVariableQuadraticFunction | |
FromJSON TwoVariableLinearFunction | |
FromJSON TwoVariableQuadraticFunction | |
FromJSON ExBudget | |
Defined in PlutusCore.Evaluation.Machine.ExBudget | |
FromJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
FromJSON ExMemory | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
FromJSON SatInt | |
Defined in Data.SatInt | |
FromJSON CovLoc | |
Defined in PlutusTx.Coverage | |
FromJSON CoverageAnnotation | |
Defined in PlutusTx.Coverage Methods parseJSON :: Value -> Parser CoverageAnnotation # parseJSONList :: Value -> Parser [CoverageAnnotation] # | |
FromJSON CoverageData | |
Defined in PlutusTx.Coverage | |
FromJSON CoverageIndex | |
Defined in PlutusTx.Coverage Methods parseJSON :: Value -> Parser CoverageIndex # parseJSONList :: Value -> Parser [CoverageIndex] # | |
FromJSON CoverageMetadata | |
Defined in PlutusTx.Coverage Methods parseJSON :: Value -> Parser CoverageMetadata # parseJSONList :: Value -> Parser [CoverageMetadata] # | |
FromJSON CoverageReport | |
Defined in PlutusTx.Coverage Methods parseJSON :: Value -> Parser CoverageReport # parseJSONList :: Value -> Parser [CoverageReport] # | |
FromJSON Metadata | |
Defined in PlutusTx.Coverage | |
FromJSON Rational | This mimics the behaviour of Aeson's instance for |
Defined in PlutusTx.Ratio | |
FromJSON Scientific | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON BaseUrl |
|
Defined in Servant.Client.Core.BaseUrl | |
FromJSON StudentT | |
Defined in Statistics.Distribution.StudentT | |
FromJSON AdditionalProperties | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser AdditionalProperties # parseJSONList :: Value -> Parser [AdditionalProperties] # | |
FromJSON ApiKeyLocation | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser ApiKeyLocation # parseJSONList :: Value -> Parser [ApiKeyLocation] # | |
FromJSON ApiKeyParams | |
Defined in Data.Swagger.Internal | |
FromJSON Contact | |
Defined in Data.Swagger.Internal | |
FromJSON Example | |
Defined in Data.Swagger.Internal | |
FromJSON ExternalDocs | |
Defined in Data.Swagger.Internal | |
FromJSON Header | |
Defined in Data.Swagger.Internal | |
FromJSON Host | |
Defined in Data.Swagger.Internal | |
FromJSON Info | |
Defined in Data.Swagger.Internal | |
FromJSON License | |
Defined in Data.Swagger.Internal | |
FromJSON MimeList | |
Defined in Data.Swagger.Internal | |
FromJSON OAuth2Flow | |
Defined in Data.Swagger.Internal | |
FromJSON OAuth2Params | |
Defined in Data.Swagger.Internal | |
FromJSON Operation | |
Defined in Data.Swagger.Internal | |
FromJSON Param | |
Defined in Data.Swagger.Internal | |
FromJSON ParamAnySchema | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser ParamAnySchema # parseJSONList :: Value -> Parser [ParamAnySchema] # | |
FromJSON ParamLocation | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser ParamLocation # parseJSONList :: Value -> Parser [ParamLocation] # | |
FromJSON ParamOtherSchema | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser ParamOtherSchema # parseJSONList :: Value -> Parser [ParamOtherSchema] # | |
FromJSON PathItem | |
Defined in Data.Swagger.Internal | |
FromJSON Reference | |
Defined in Data.Swagger.Internal | |
FromJSON Response | |
Defined in Data.Swagger.Internal | |
FromJSON Responses | |
Defined in Data.Swagger.Internal | |
FromJSON Schema | |
Defined in Data.Swagger.Internal | |
FromJSON Scheme | |
Defined in Data.Swagger.Internal | |
FromJSON SecurityDefinitions | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser SecurityDefinitions # parseJSONList :: Value -> Parser [SecurityDefinitions] # | |
FromJSON SecurityRequirement | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser SecurityRequirement # parseJSONList :: Value -> Parser [SecurityRequirement] # | |
FromJSON SecurityScheme | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser SecurityScheme # parseJSONList :: Value -> Parser [SecurityScheme] # | |
FromJSON SecuritySchemeType | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser SecuritySchemeType # parseJSONList :: Value -> Parser [SecuritySchemeType] # | |
FromJSON Swagger | |
Defined in Data.Swagger.Internal | |
FromJSON Tag | |
Defined in Data.Swagger.Internal | |
FromJSON URL | |
Defined in Data.Swagger.Internal | |
FromJSON Xml | |
Defined in Data.Swagger.Internal | |
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Text | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON ShortText | Since: aeson-2.0.2.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON CalendarDiffDays | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser CalendarDiffDays # parseJSONList :: Value -> Parser [CalendarDiffDays] # | |
FromJSON Day | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Month | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Quarter | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON QuarterOfYear | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser QuarterOfYear # parseJSONList :: Value -> Parser [QuarterOfYear] # | |
FromJSON DayOfWeek | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON DiffTime | This instance includes a bounds check to prevent maliciously
large inputs to fill up the memory of the target system. You can
newtype |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON NominalDiffTime | This instance includes a bounds check to prevent maliciously
large inputs to fill up the memory of the target system. You can
newtype |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser NominalDiffTime # parseJSONList :: Value -> Parser [NominalDiffTime] # | |
FromJSON SystemTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON UTCTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON CalendarDiffTime | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser CalendarDiffTime # parseJSONList :: Value -> Parser [CalendarDiffTime] # | |
FromJSON LocalTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON TimeOfDay | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON ZonedTime | Supported string formats:
The first space may instead be a |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON ConfigOptionRep | |
Defined in Cardano.Logging.ConfigurationParser | |
FromJSON ConfigRepresentation | |
Defined in Cardano.Logging.ConfigurationParser | |
FromJSON BackendConfig | |
Defined in Cardano.Logging.Types Methods parseJSON :: Value -> Parser BackendConfig # parseJSONList :: Value -> Parser [BackendConfig] # | |
FromJSON DetailLevel | |
Defined in Cardano.Logging.Types | |
FromJSON ForwarderAddr | |
Defined in Cardano.Logging.Types Methods parseJSON :: Value -> Parser ForwarderAddr # parseJSONList :: Value -> Parser [ForwarderAddr] # | |
FromJSON ForwarderMode | |
Defined in Cardano.Logging.Types Methods parseJSON :: Value -> Parser ForwarderMode # parseJSONList :: Value -> Parser [ForwarderMode] # | |
FromJSON SeverityF | |
Defined in Cardano.Logging.Types | |
FromJSON SeverityS | |
Defined in Cardano.Logging.Types | |
FromJSON TraceOptionForwarder | |
Defined in Cardano.Logging.Types Methods parseJSON :: Value -> Parser TraceOptionForwarder # parseJSONList :: Value -> Parser [TraceOptionForwarder] # | |
FromJSON Verbosity | |
Defined in Cardano.Logging.Types | |
FromJSON UUID | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Integer | This instance includes a bounds check to prevent maliciously
large inputs to fill up the memory of the target system. You can
newtype |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Natural | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON () | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Bool | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Char | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Double | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Float | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Int | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON Word | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON v => FromJSON (KeyMap v) | Since: aeson-2.0.1.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Confidential a) # | |
Defined in GeniusYield.GYConfig Methods parseJSON :: Value -> Parser (Confidential a) # parseJSONList :: Value -> Parser [Confidential a] # omittedField :: Maybe (Confidential a) # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYExtendedVerificationKeyToApi kr)) => FromJSON (GYExtendedVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods parseJSON :: Value -> Parser (GYExtendedVerificationKey kr) # parseJSONList :: Value -> Parser [GYExtendedVerificationKey kr] # omittedField :: Maybe (GYExtendedVerificationKey kr) # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYSigningKeyToApi kr)) => FromJSON (GYSigningKey kr) # |
|
Defined in GeniusYield.Types.Key Methods parseJSON :: Value -> Parser (GYSigningKey kr) # parseJSONList :: Value -> Parser [GYSigningKey kr] # omittedField :: Maybe (GYSigningKey kr) # | |
(SingGYKeyRoleI kr, SerialiseAsCBOR (GYVerificationKeyToApi kr)) => FromJSON (GYVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods parseJSON :: Value -> Parser (GYVerificationKey kr) # parseJSONList :: Value -> Parser [GYVerificationKey kr] # omittedField :: Maybe (GYVerificationKey kr) # | |
SingGYKeyRoleI kr => FromJSON (GYKeyHash kr) # |
Invalid characters:
|
Defined in GeniusYield.Types.KeyHash | |
FromJSON a => FromJSON (First a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Last a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Max a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Min a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (WrappedMonoid a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (WrappedMonoid a) # parseJSONList :: Value -> Parser [WrappedMonoid a] # omittedField :: Maybe (WrappedMonoid a) # | |
FromJSON (Script KeyHash) | |
FromJSON (Script Cosigner) | |
FromJSON (Address ByronAddr) | |
FromJSON (Address ShelleyAddr) | |
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (Address ShelleyAddr) # parseJSONList :: Value -> Parser [Address ShelleyAddr] # omittedField :: Maybe (Address ShelleyAddr) # | |
IsShelleyBasedEra era => FromJSON (AddressInEra era) | |
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (AddressInEra era) # parseJSONList :: Value -> Parser [AddressInEra era] # omittedField :: Maybe (AddressInEra era) # | |
FromJSON (Authors CIP108) | |
FromJSON (Body CIP119) | |
FromJSON (Body CIP108) | |
FromJSON (GovActionMetadata CIP119) | |
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Methods parseJSON :: Value -> Parser (GovActionMetadata CIP119) # parseJSONList :: Value -> Parser [GovActionMetadata CIP119] # | |
FromJSON (GovActionMetadata CIP108) | |
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (GovActionMetadata CIP108) # parseJSONList :: Value -> Parser [GovActionMetadata CIP108] # | |
FromJSON (HashAlgorithm CIP119) | |
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Methods parseJSON :: Value -> Parser (HashAlgorithm CIP119) # parseJSONList :: Value -> Parser [HashAlgorithm CIP119] # | |
FromJSON (HashAlgorithm CIP108) | |
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (HashAlgorithm CIP108) # parseJSONList :: Value -> Parser [HashAlgorithm CIP108] # | |
FromJSON (Hash BlockHeader) | |
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) # parseJSONList :: Value -> Parser [Hash BlockHeader] # omittedField :: Maybe (Hash BlockHeader) # | |
FromJSON (Hash DRepKey) | |
FromJSON (Hash GenesisKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash GenesisKey) # parseJSONList :: Value -> Parser [Hash GenesisKey] # omittedField :: Maybe (Hash GenesisKey) # | |
FromJSON (Hash PaymentKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash PaymentKey) # parseJSONList :: Value -> Parser [Hash PaymentKey] # omittedField :: Maybe (Hash PaymentKey) # | |
FromJSON (Hash StakePoolKey) | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolKey) # parseJSONList :: Value -> Parser [Hash StakePoolKey] # omittedField :: Maybe (Hash StakePoolKey) # | |
FromJSON (Hash ScriptData) | |
Defined in Cardano.Api.Internal.ScriptData Methods parseJSON :: Value -> Parser (Hash ScriptData) # parseJSONList :: Value -> Parser [Hash ScriptData] # omittedField :: Maybe (Hash ScriptData) # | |
IsCardanoEra era => FromJSON (ReferenceScript era) | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser (ReferenceScript era) # parseJSONList :: Value -> Parser [ReferenceScript era] # omittedField :: Maybe (ReferenceScript era) # | |
IsShelleyBasedEra era => FromJSON (TxOutValue era) | |
Defined in Cardano.Api.Internal.Tx.Body Methods parseJSON :: Value -> Parser (TxOutValue era) # parseJSONList :: Value -> Parser [TxOutValue era] # omittedField :: Maybe (TxOutValue era) # | |
IsShelleyBasedEra era => FromJSON (UTxO era) | |
Defined in Cardano.Api.Internal.Tx.UTxO | |
FromJSON a => FromJSON (RedeemSignature a) | |
Defined in Cardano.Crypto.Signing.Redeem.Signature Methods parseJSON :: Value -> Parser (RedeemSignature a) # parseJSONList :: Value -> Parser [RedeemSignature a] # omittedField :: Maybe (RedeemSignature a) # | |
FromJSON (Signature w) | |
Defined in Cardano.Crypto.Signing.Signature | |
Era era => FromJSON (Committee era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures | |
Era era => FromJSON (Constitution era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods parseJSON :: Value -> Parser (Constitution era) # parseJSONList :: Value -> Parser [Constitution era] # omittedField :: Maybe (Constitution era) # | |
FromJSON (UpgradeConwayPParams Identity) | |
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser (UpgradeConwayPParams Identity) # parseJSONList :: Value -> Parser [UpgradeConwayPParams Identity] # | |
(FromJSON a, HasZero a) => FromJSON (NonZero a) | |
Defined in Cardano.Ledger.BaseTypes.NonZero | |
FromJSON (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods parseJSON :: Value -> Parser (CompactForm Coin) # parseJSONList :: Value -> Parser [CompactForm Coin] # omittedField :: Maybe (CompactForm Coin) # | |
FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) | |
Defined in Cardano.Ledger.Core.PParams | |
FromJSON (PParamsHKD StrictMaybe era) => FromJSON (PParamsUpdate era) | |
Defined in Cardano.Ledger.Core.PParams Methods parseJSON :: Value -> Parser (PParamsUpdate era) # parseJSONList :: Value -> Parser [PParamsUpdate era] # omittedField :: Maybe (PParamsUpdate era) # | |
FromJSON (Credential kr) | |
Defined in Cardano.Ledger.Credential Methods parseJSON :: Value -> Parser (Credential kr) # parseJSONList :: Value -> Parser [Credential kr] # omittedField :: Maybe (Credential kr) # | |
FromJSON (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
FromJSON (SafeHash i) | |
Defined in Cardano.Ledger.Hashes | |
FromJSON (VRFVerKeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods parseJSON :: Value -> Parser (VRFVerKeyHash r) # parseJSONList :: Value -> Parser [VRFVerKeyHash r] # omittedField :: Maybe (VRFVerKeyHash r) # | |
FromJSON a => FromJSON (ExUnits' a) | |
Defined in Cardano.Ledger.Plutus.ExUnits | |
FromJSON (TransitionConfig ShelleyEra) | |
Defined in Cardano.Ledger.Shelley.Transition Methods parseJSON :: Value -> Parser (TransitionConfig ShelleyEra) # parseJSONList :: Value -> Parser [TransitionConfig ShelleyEra] # | |
FromJSON (OnOff a) | |
Defined in Cardano.Tracing.Config | |
FromJSON a => FromJSON (WithOrigin a) | |
Defined in Cardano.Slotting.Slot Methods parseJSON :: Value -> Parser (WithOrigin a) # parseJSONList :: Value -> Parser [WithOrigin a] # omittedField :: Maybe (WithOrigin a) # | |
FromJSON a => FromJSON (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods parseJSON :: Value -> Parser (StrictMaybe a) # parseJSONList :: Value -> Parser [StrictMaybe a] # omittedField :: Maybe (StrictMaybe a) # | |
FromJSON a => FromJSON (StrictSeq a) | |
Defined in Data.Sequence.Strict | |
FromJSON a => FromJSON (LogEntry a) | |
Defined in Testnet.Property.Assert | |
FromJSON a => FromJSON (IntMap a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Seq a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Ord a, FromJSON a) => FromJSON (Set a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON v => FromJSON (Tree v) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON1 f => FromJSON (Fix f) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, Functor f) => FromJSON (Mu f) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, Functor f) => FromJSON (Nu f) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (DNonEmpty a) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (DList a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (NonEmpty a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Identity a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (First a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Last a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Down a) | Since: aeson-2.2.0.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Dual a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Product a) | Since: aeson-2.2.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Sum a) | Since: aeson-2.2.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) | Since: aeson-2.1.0.0 |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Generically a) # parseJSONList :: Value -> Parser [Generically a] # omittedField :: Maybe (Generically a) # | |
(FromJSON a, Integral a) => FromJSON (Ratio a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Eq a, Hashable a, FromJSON a) => FromJSON (InsOrdHashSet a) | |
Defined in Data.HashSet.InsOrd Methods parseJSON :: Value -> Parser (InsOrdHashSet a) # parseJSONList :: Value -> Parser [InsOrdHashSet a] # omittedField :: Maybe (InsOrdHashSet a) # | |
FromJSON a => FromJSON (LOContent a) | |
Defined in Cardano.BM.Data.LogItem | |
FromJSON a => FromJSON (LogObject a) | |
Defined in Cardano.BM.Data.LogItem | |
FromJSON a => FromJSON (Resources a) | |
Defined in Cardano.BM.Stats.Resources | |
FromJSON a => FromJSON (Item a) | |
Defined in Katip.Core | |
FromJSON (Bech32StringOf a) | |
Defined in Maestro.Types.Common Methods parseJSON :: Value -> Parser (Bech32StringOf a) # parseJSONList :: Value -> Parser [Bech32StringOf a] # omittedField :: Maybe (Bech32StringOf a) # | |
FromJSON (HashStringOf a) | |
Defined in Maestro.Types.Common Methods parseJSON :: Value -> Parser (HashStringOf a) # parseJSONList :: Value -> Parser [HashStringOf a] # omittedField :: Maybe (HashStringOf a) # | |
FromJSON (HexStringOf a) | |
Defined in Maestro.Types.Common Methods parseJSON :: Value -> Parser (HexStringOf a) # parseJSONList :: Value -> Parser [HexStringOf a] # omittedField :: Maybe (HexStringOf a) # | |
FromJSON (TaggedText description) | |
Defined in Maestro.Types.V1.Common Methods parseJSON :: Value -> Parser (TaggedText description) # parseJSONList :: Value -> Parser [TaggedText description] # omittedField :: Maybe (TaggedText description) # | |
FromJSON i => FromJSON (MemoryCpuWith i) | |
Defined in Maestro.Types.V1.General Methods parseJSON :: Value -> Parser (MemoryCpuWith i) # parseJSONList :: Value -> Parser [MemoryCpuWith i] # omittedField :: Maybe (MemoryCpuWith i) # | |
(Eq p, FromJSON p, AesonDefaultValue p) => FromJSON (OAuth2Flow p) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (OAuth2Flow p) # parseJSONList :: Value -> Parser [OAuth2Flow p] # omittedField :: Maybe (OAuth2Flow p) # | |
FromJSON (Referenced Callback) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Callback) # parseJSONList :: Value -> Parser [Referenced Callback] # omittedField :: Maybe (Referenced Callback) # | |
FromJSON (Referenced Example) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Example) # parseJSONList :: Value -> Parser [Referenced Example] # omittedField :: Maybe (Referenced Example) # | |
FromJSON (Referenced Header) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Header) # parseJSONList :: Value -> Parser [Referenced Header] # omittedField :: Maybe (Referenced Header) # | |
FromJSON (Referenced Link) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Link) # parseJSONList :: Value -> Parser [Referenced Link] # omittedField :: Maybe (Referenced Link) # | |
FromJSON (Referenced Param) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Param) # parseJSONList :: Value -> Parser [Referenced Param] # omittedField :: Maybe (Referenced Param) # | |
FromJSON (Referenced RequestBody) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced RequestBody) # parseJSONList :: Value -> Parser [Referenced RequestBody] # | |
FromJSON (Referenced Response) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Response) # parseJSONList :: Value -> Parser [Referenced Response] # omittedField :: Maybe (Referenced Response) # | |
FromJSON (Referenced Schema) | |
Defined in Data.OpenApi.Internal Methods parseJSON :: Value -> Parser (Referenced Schema) # parseJSONList :: Value -> Parser [Referenced Schema] # omittedField :: Maybe (Referenced Schema) # | |
FromJSON (BuiltinCostModelBase CostingFun) | |
Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel Methods parseJSON :: Value -> Parser (BuiltinCostModelBase CostingFun) # parseJSONList :: Value -> Parser [BuiltinCostModelBase CostingFun] # | |
FromJSON (CekMachineCostsBase Identity) | |
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts Methods parseJSON :: Value -> Parser (CekMachineCostsBase Identity) # parseJSONList :: Value -> Parser [CekMachineCostsBase Identity] # | |
FromJSON a => FromJSON (Array a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Prim a, FromJSON a) => FromJSON (PrimArray a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (SmallArray a) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (SmallArray a) # parseJSONList :: Value -> Parser [SmallArray a] # omittedField :: Maybe (SmallArray a) # | |
FromJSON d => FromJSON (LinearTransform d) | |
Defined in Statistics.Distribution.Transform Methods parseJSON :: Value -> Parser (LinearTransform d) # parseJSONList :: Value -> Parser [LinearTransform d] # omittedField :: Maybe (LinearTransform d) # | |
FromJSON a => FromJSON (Maybe a) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON (CollectionFormat ('SwaggerKindNormal t)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (CollectionFormat ('SwaggerKindNormal t)) # parseJSONList :: Value -> Parser [CollectionFormat ('SwaggerKindNormal t)] # omittedField :: Maybe (CollectionFormat ('SwaggerKindNormal t)) # | |
FromJSON (CollectionFormat ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (CollectionFormat ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [CollectionFormat ('SwaggerKindParamOtherSchema :: SwaggerKind Type)] # omittedField :: Maybe (CollectionFormat ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # | |
(FromJSON (SwaggerType ('SwaggerKindNormal t)), FromJSON (SwaggerItems ('SwaggerKindNormal t))) => FromJSON (ParamSchema ('SwaggerKindNormal t)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (ParamSchema ('SwaggerKindNormal t)) # parseJSONList :: Value -> Parser [ParamSchema ('SwaggerKindNormal t)] # omittedField :: Maybe (ParamSchema ('SwaggerKindNormal t)) # | |
FromJSON (ParamSchema ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (ParamSchema ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [ParamSchema ('SwaggerKindParamOtherSchema :: SwaggerKind Type)] # omittedField :: Maybe (ParamSchema ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # | |
FromJSON (ParamSchema ('SwaggerKindSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (ParamSchema ('SwaggerKindSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [ParamSchema ('SwaggerKindSchema :: SwaggerKind Type)] # omittedField :: Maybe (ParamSchema ('SwaggerKindSchema :: SwaggerKind Type)) # | |
FromJSON (Referenced Param) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (Referenced Param) # parseJSONList :: Value -> Parser [Referenced Param] # omittedField :: Maybe (Referenced Param) # | |
FromJSON (Referenced Response) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (Referenced Response) # parseJSONList :: Value -> Parser [Referenced Response] # omittedField :: Maybe (Referenced Response) # | |
FromJSON (Referenced Schema) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (Referenced Schema) # parseJSONList :: Value -> Parser [Referenced Schema] # omittedField :: Maybe (Referenced Schema) # | |
(FromJSON (CollectionFormat ('SwaggerKindNormal t)), FromJSON (ParamSchema ('SwaggerKindNormal t))) => FromJSON (SwaggerItems ('SwaggerKindNormal t)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerItems ('SwaggerKindNormal t)) # parseJSONList :: Value -> Parser [SwaggerItems ('SwaggerKindNormal t)] # omittedField :: Maybe (SwaggerItems ('SwaggerKindNormal t)) # | |
FromJSON (SwaggerItems ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerItems ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [SwaggerItems ('SwaggerKindParamOtherSchema :: SwaggerKind Type)] # omittedField :: Maybe (SwaggerItems ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # | |
FromJSON (SwaggerItems ('SwaggerKindSchema :: SwaggerKind Type)) |
|
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerItems ('SwaggerKindSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [SwaggerItems ('SwaggerKindSchema :: SwaggerKind Type)] # omittedField :: Maybe (SwaggerItems ('SwaggerKindSchema :: SwaggerKind Type)) # | |
FromJSON (SwaggerType ('SwaggerKindNormal t)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerType ('SwaggerKindNormal t)) # parseJSONList :: Value -> Parser [SwaggerType ('SwaggerKindNormal t)] # omittedField :: Maybe (SwaggerType ('SwaggerKindNormal t)) # | |
FromJSON (SwaggerType ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerType ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [SwaggerType ('SwaggerKindParamOtherSchema :: SwaggerKind Type)] # omittedField :: Maybe (SwaggerType ('SwaggerKindParamOtherSchema :: SwaggerKind Type)) # | |
FromJSON (SwaggerType ('SwaggerKindSchema :: SwaggerKind Type)) | |
Defined in Data.Swagger.Internal Methods parseJSON :: Value -> Parser (SwaggerType ('SwaggerKindSchema :: SwaggerKind Type)) # parseJSONList :: Value -> Parser [SwaggerType ('SwaggerKindSchema :: SwaggerKind Type)] # omittedField :: Maybe (SwaggerType ('SwaggerKindSchema :: SwaggerKind Type)) # | |
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Prim a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Storable a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Vector Vector a, FromJSON a) => FromJSON (Vector a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Maybe a) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON (Solo a) | Since: aeson-2.0.2.0 |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON a => FromJSON [a] | |
Defined in Data.Aeson.Types.FromJSON | |
HasResolution a => FromJSON (Fixed a) | This instance includes a bounds check to prevent maliciously
large inputs to fill up the memory of the target system. You can
newtype |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON (File content direction) | |
Defined in Cardano.Api.Internal.IO.Base | |
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) | |
HashAlgorithm h => FromJSON (Hash h a) | |
Defined in Cardano.Crypto.Hash.Class | |
HashAlgorithm algo => FromJSON (AbstractHash algo a) | |
Defined in Cardano.Crypto.Hashing Methods parseJSON :: Value -> Parser (AbstractHash algo a) # parseJSONList :: Value -> Parser [AbstractHash algo a] # omittedField :: Maybe (AbstractHash algo a) # | |
(FromJSON v, FromJSON k, FromJSONKey k) => FromJSON (ListMap k v) | |
Defined in Data.ListMap | |
FromJSON (AlonzoPParams Identity era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods parseJSON :: Value -> Parser (AlonzoPParams Identity era) # parseJSONList :: Value -> Parser [AlonzoPParams Identity era] # omittedField :: Maybe (AlonzoPParams Identity era) # | |
FromJSON (BabbagePParams Identity era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods parseJSON :: Value -> Parser (BabbagePParams Identity era) # parseJSONList :: Value -> Parser [BabbagePParams Identity era] # omittedField :: Maybe (BabbagePParams Identity era) # | |
FromJSON b => FromJSON (Annotated b ()) | |
Defined in Cardano.Ledger.Binary.Decoding.Annotated | |
Era era => FromJSON (ConwayPParams Identity era) | |
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser (ConwayPParams Identity era) # parseJSONList :: Value -> Parser [ConwayPParams Identity era] # omittedField :: Maybe (ConwayPParams Identity era) # | |
Bounded (BoundedRatio b Word64) => FromJSON (BoundedRatio b Word64) | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON a => FromJSON (Mismatch r a) | |
Defined in Cardano.Ledger.BaseTypes | |
FromJSON (ShelleyPParams Identity era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods parseJSON :: Value -> Parser (ShelleyPParams Identity era) # parseJSONList :: Value -> Parser [ShelleyPParams Identity era] # omittedField :: Maybe (ShelleyPParams Identity era) # | |
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON (Proxy a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Eq k, Hashable k, FromJSONKey k, FromJSON v) => FromJSON (InsOrdHashMap k v) | |
Defined in Data.HashMap.Strict.InsOrd Methods parseJSON :: Value -> Parser (InsOrdHashMap k v) # parseJSONList :: Value -> Parser [InsOrdHashMap k v] # omittedField :: Maybe (InsOrdHashMap k v) # | |
(FromJSONKey k, Ord k, FromJSON a) => FromJSON (MonoidalMap k a) | |
Defined in Data.Map.Monoidal Methods parseJSON :: Value -> Parser (MonoidalMap k a) # parseJSONList :: Value -> Parser [MonoidalMap k a] # omittedField :: Maybe (MonoidalMap k a) # | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b) => FromJSON (These a b) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b) => FromJSON (Pair a b) | Since: aeson-1.5.3.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b) => FromJSON (These a b) | Since: aeson-1.5.1.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON (Address, NutlinkTicker) | |
Defined in Blockfrost.Types.NutLink Methods parseJSON :: Value -> Parser (Address, NutlinkTicker) # parseJSONList :: Value -> Parser [(Address, NutlinkTicker)] # omittedField :: Maybe (Address, NutlinkTicker) # | |
FromJSON (Text, Metric) | |
(FromJSON a, FromJSON b) => FromJSON (a, b) | |
Defined in Data.Aeson.Types.FromJSON | |
(Typeable t, FromJSON a) => FromJSON (THKD t StrictMaybe a) | |
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser (THKD t StrictMaybe a) # parseJSONList :: Value -> Parser [THKD t StrictMaybe a] # omittedField :: Maybe (THKD t StrictMaybe a) # | |
(Typeable t, FromJSON a) => FromJSON (THKD t Identity a) | |
(AesonOptions t, Generic a, GFromJSON Zero (Rep a)) => FromJSON (CustomJSON t a) | |
Defined in Deriving.Aeson Methods parseJSON :: Value -> Parser (CustomJSON t a) # parseJSONList :: Value -> Parser [CustomJSON t a] # omittedField :: Maybe (CustomJSON t a) # | |
FromJSON a => FromJSON (Const a b) | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSON b => FromJSON (Tagged a b) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (These1 f g a) | Since: aeson-1.5.1.0 |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) | |
Defined in Data.Aeson.Types.FromJSON | |
(Vector vk k, Vector vv v, Ord k, FromJSONKey k, FromJSON v) => FromJSON (VMap vk vv k v) | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Defined in Data.Aeson.Types.FromJSON | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Defined in Data.Aeson.Types.FromJSON |
(>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 #
Left-to-right composition
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
@since base-4.9.0.0
isHexDigit :: Char -> Bool #
Selects ASCII hexadecimal digits,
i.e. '0'
..'9'
, 'a'
..'f'
, 'A'
..'F'
.
fromRight :: b -> Either a b -> b #
Return the contents of a Right
-value or a default value otherwise.
@since base-4.10.0.0
Examples
Basic usage:
>>>
fromRight 1 (Right 3)
3>>>
fromRight 1 (Left "foo")
1
data (a :: k) :~: (b :: k) where infix 4 #
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
@since base-4.7.0.0
Instances
Category ((:~:) :: k -> k -> Type) | @since base-4.7.0.0 |
TestEquality ((:~:) a :: k -> Type) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Equality | |
EqP ((:~:) a :: k -> Type) | |
GNFData ((:~:) a :: k -> Type) | Since: some-1.0.3 |
Defined in Data.GADT.DeepSeq | |
GCompare ((:~:) a :: k -> Type) | |
GEq ((:~:) a :: k -> Type) | |
GRead ((:~:) a :: k -> Type) | |
Defined in Data.GADT.Internal Methods greadsPrec :: Int -> GReadS ((:~:) a) # | |
GShow ((:~:) a :: k -> Type) | |
Defined in Data.GADT.Internal Methods gshowsPrec :: forall (a0 :: k). Int -> (a :~: a0) -> ShowS # | |
OrdP ((:~:) a :: k -> Type) | |
NFData2 ((:~:) :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData1 ((:~:) a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData (a :~: b) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
a ~ b => Bounded (a :~: b) | @since base-4.7.0.0 |
a ~ b => Enum (a :~: b) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Equality Methods succ :: (a :~: b) -> a :~: b # pred :: (a :~: b) -> a :~: b # fromEnum :: (a :~: b) -> Int # enumFrom :: (a :~: b) -> [a :~: b] # enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] # | |
a ~ b => Read (a :~: b) | @since base-4.7.0.0 |
Show (a :~: b) | @since base-4.7.0.0 |
Eq (a :~: b) | @since base-4.7.0.0 |
Ord (a :~: b) | @since base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Equality |
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The largest element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>
maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"Longest"
WARNING: This function is partial for possibly-empty structures like lists.
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The least element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>
minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"!"
WARNING: This function is partial for possibly-empty structures like lists.
Typeclass of printf
-formattable values. The formatArg
method
takes a value and a field format descriptor and either fails due
to a bad descriptor or produces a ShowS
as the result. The
default parseFormat
expects no modifiers: this is the normal
case. Minimal instance: formatArg
.
Minimal complete definition
Methods
formatArg :: a -> FieldFormatter #
Since: base-4.7.0.0
parseFormat :: a -> ModifierParser #
Since: base-4.7.0.0
Instances
PrintfArg GYBalancingError # | |
Defined in GeniusYield.Transaction.Common Methods | |
PrintfArg GYAddress # | This instance is using for logging
|
Defined in GeniusYield.Types.Address | |
PrintfArg GYAddressBech32 # | |
Defined in GeniusYield.Types.Address Methods | |
PrintfArg GYStakeAddress # | This instance is using for logging
|
Defined in GeniusYield.Types.Address Methods | |
PrintfArg GYStakeAddressBech32 # | |
Defined in GeniusYield.Types.Address Methods | |
PrintfArg GYLogNamespace # |
|
Defined in GeniusYield.Types.Logging Methods | |
PrintfArg GYNatural # | |
Defined in GeniusYield.Types.Natural | |
PrintfArg GYPubKeyHash # |
|
Defined in GeniusYield.Types.PubKeyHash | |
PrintfArg GYRational # |
|
Defined in GeniusYield.Types.Rational | |
PrintfArg GYScriptHash # |
|
Defined in GeniusYield.Types.Script.ScriptHash | |
PrintfArg GYSlot # | |
Defined in GeniusYield.Types.Slot | |
PrintfArg GYTime # |
|
Defined in GeniusYield.Types.Time | |
PrintfArg GYTx # | |
Defined in GeniusYield.Types.Tx | |
PrintfArg GYTxId # |
|
Defined in GeniusYield.Types.Tx | |
PrintfArg GYTxWitness # | |
Defined in GeniusYield.Types.Tx | |
PrintfArg GYTxOutRef # | |
Defined in GeniusYield.Types.TxOutRef | |
PrintfArg GYTxOutRefCbor # | |
Defined in GeniusYield.Types.TxOutRef Methods | |
PrintfArg GYUTxOs # | |
Defined in GeniusYield.Types.UTxO | |
PrintfArg GYAssetClass # |
|
Defined in GeniusYield.Types.Value | |
PrintfArg GYValue # |
|
Defined in GeniusYield.Types.Value | |
PrintfArg Int16 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Int32 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Int64 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Int8 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Word16 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Word32 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Word64 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Word8 | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg ShortText | Since: text-short-0.1.2 |
Defined in Data.Text.Short.Internal | |
PrintfArg Integer | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Natural | Since: base-4.8.0.0 |
Defined in Text.Printf | |
PrintfArg Char | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Double | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Float | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Int | Since: base-2.1 |
Defined in Text.Printf | |
PrintfArg Word | Since: base-2.1 |
Defined in Text.Printf | |
SingGYKeyRoleI kr => PrintfArg (GYCredential kr) # |
|
Defined in GeniusYield.Types.Credential Methods formatArg :: GYCredential kr -> FieldFormatter # parseFormat :: GYCredential kr -> ModifierParser # | |
PrintfArg (GYExtendedVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods formatArg :: GYExtendedVerificationKey kr -> FieldFormatter # parseFormat :: GYExtendedVerificationKey kr -> ModifierParser # | |
PrintfArg (GYSigningKey kr) # |
|
Defined in GeniusYield.Types.Key Methods formatArg :: GYSigningKey kr -> FieldFormatter # parseFormat :: GYSigningKey kr -> ModifierParser # | |
PrintfArg (GYVerificationKey kr) # |
|
Defined in GeniusYield.Types.Key Methods formatArg :: GYVerificationKey kr -> FieldFormatter # parseFormat :: GYVerificationKey kr -> ModifierParser # | |
PrintfArg (GYKeyHash kr) # |
|
Defined in GeniusYield.Types.KeyHash | |
IsChar c => PrintfArg [c] | Since: base-2.1 |
Defined in Text.Printf |
printf :: PrintfType r => String -> r #
Format a variable number of arguments with the C-style formatting string.
>>>
printf "%s, %d, %.4f" "hello" 123 pi
hello, 123, 3.1416
The return value is either String
or (
(which
should be IO
a)(
, but Haskell's type system
makes this hard).IO
())
The format string consists of ordinary characters and
conversion specifications, which specify how to format
one of the arguments to printf
in the output string. A
format specification is introduced by the %
character;
this character can be self-escaped into the format string
using %%
. A format specification ends with a
format character that provides the primary information about
how to format the value. The rest of the conversion
specification is optional. In order, one may have flag
characters, a width specifier, a precision specifier, and
type-specific modifier characters.
Unlike C printf(3)
, the formatting of this printf
is driven by the argument type; formatting is type specific. The
types formatted by printf
"out of the box" are:
printf
is also extensible to support other types: see below.
A conversion specification begins with the
character %
, followed by zero or more of the following flags:
- left adjust (default is right adjust) + always use a sign (+ or -) for signed conversions space leading space for positive numbers in signed conversions 0 pad with zeros rather than spaces # use an \"alternate form\": see below
When both flags are given, -
overrides 0
and +
overrides space.
A negative width specifier in a *
conversion is treated as
positive but implies the left adjust flag.
The "alternate form" for unsigned radix conversions is
as in C printf(3)
:
%o prefix with a leading 0 if needed %x prefix with a leading 0x if nonzero %X prefix with a leading 0X if nonzero %b prefix with a leading 0b if nonzero %[eEfFgG] ensure that the number contains a decimal point
Any flags are followed optionally by a field width:
num field width * as num, but taken from argument list
The field width is a minimum, not a maximum: it will be expanded as needed to avoid mutilating a value.
Any field width is followed optionally by a precision:
.num precision . same as .0 .* as num, but taken from argument list
Negative precision is taken as 0. The meaning of the precision depends on the conversion type.
Integral minimum number of digits to show RealFloat number of digits after the decimal point String maximum number of characters
The precision for Integral types is accomplished by zero-padding. If both precision and zero-pad are given for an Integral field, the zero-pad is ignored.
Any precision is followed optionally for Integral types by a width modifier; the only use of this modifier being to set the implicit size of the operand for conversion of a negative operand to unsigned:
hh Int8 h Int16 l Int32 ll Int64 L Int64
The specification ends with a format character:
c character Integral d decimal Integral o octal Integral x hexadecimal Integral X hexadecimal Integral b binary Integral u unsigned decimal Integral f floating point RealFloat F floating point RealFloat g general format float RealFloat G general format float RealFloat e exponent format float RealFloat E exponent format float RealFloat s string String v default format any type
The "%v" specifier is provided for all built-in types, and should be provided for user-defined type formatters as well. It picks a "best" representation for the given type. For the built-in types the "%v" specifier is converted as follows:
c Char u other unsigned Integral d other signed Integral g RealFloat s String
Mismatch between the argument types and the format string, as well as any other syntactic or semantic errors in the format string, will cause an exception to be thrown at runtime.
Note that the formatting for RealFloat
types is
currently a bit different from that of C printf(3)
,
conforming instead to showEFloat
,
showFFloat
and showGFloat
(and their
alternate versions showFFloatAlt
and
showGFloatAlt
). This is hard to fix: the fixed
versions would format in a backward-incompatible way.
In any case the Haskell behavior is generally more
sensible than the C behavior. A brief summary of some
key differences:
- Haskell
printf
never uses the default "6-digit" precision used by C printf. - Haskell
printf
treats the "precision" specifier as indicating the number of digits after the decimal point. - Haskell
printf
prints the exponent of e-format numbers without a gratuitous plus sign, and with the minimum possible number of digits. - Haskell
printf
will place a zero after a decimal point when possible.
wither :: (Witherable t, Applicative f) => (a -> f (Maybe b)) -> t a -> f (t b) #
data Some (tag :: k -> Type) where #
Existential. This is type is useful to hide GADTs' parameters.
>>>
data Tag :: Type -> Type where TagInt :: Tag Int; TagBool :: Tag Bool
>>>
instance GShow Tag where gshowsPrec _ TagInt = showString "TagInt"; gshowsPrec _ TagBool = showString "TagBool"
>>>
classify s = case s of "TagInt" -> [mkGReadResult TagInt]; "TagBool" -> [mkGReadResult TagBool]; _ -> []
>>>
instance GRead Tag where greadsPrec _ s = [ (r, rest) | (con, rest) <- lex s, r <- classify con ]
You can either use PatternSynonyms
(available with GHC >= 8.0)
>>>
let x = Some TagInt
>>>
x
Some TagInt
>>>
case x of { Some TagInt -> "I"; Some TagBool -> "B" } :: String
"I"
or you can use functions
>>>
let y = mkSome TagBool
>>>
y
Some TagBool
>>>
withSome y $ \y' -> case y' of { TagInt -> "I"; TagBool -> "B" } :: String
"B"
The implementation of mapSome
is safe.
>>>
let f :: Tag a -> Tag a; f TagInt = TagInt; f TagBool = TagBool
>>>
mapSome f y
Some TagBool
but you can also use:
>>>
withSome y (mkSome . f)
Some TagBool
>>>
read "Some TagBool" :: Some Tag
Some TagBool
>>>
read "mkSome TagInt" :: Some Tag
Some TagInt
Instances
(Closed uni, Everywhere uni PrettyConst) => PrettyBy ConstConfig (Some (ValueOf uni)) | |
Defined in PlutusCore.Pretty.PrettyConst Methods prettyBy :: ConstConfig -> Some (ValueOf uni) -> Doc ann # prettyListBy :: ConstConfig -> [Some (ValueOf uni)] -> Doc ann # | |
GNFData tag => NFData (Some tag) | |
Defined in Data.Some.Newtype | |
Applicative m => Monoid (Some m) | |
Applicative m => Semigroup (Some m) | |
GRead f => Read (Some f) | |
GShow tag => Show (Some tag) | |
GEq tag => Eq (Some tag) | |
GCompare tag => Ord (Some tag) | |
Defined in Data.Some.Newtype | |
(Closed uni, GEq uni, Everywhere uni Eq, Everywhere uni Hashable) => Hashable (Some (ValueOf uni)) | |
(Closed uni, Everywhere uni ExMemoryUsage) => ExMemoryUsage (Some (ValueOf uni)) | |
Defined in PlutusCore.Evaluation.Machine.ExMemoryUsage Methods memoryUsage :: Some (ValueOf uni) -> CostRose # |
encodeUtf8 :: Text -> ByteString #
Encode text using UTF-8 encoding.
rightToMaybe :: Either a b -> Maybe b #
Maybe get the Right
side of an Either
.
rightToMaybe
≡either
(const
Nothing
)Just
Using Control.Lens
:
rightToMaybe
≡ preview _RightrightToMaybe
x ≡ x^?_Right
>>>
rightToMaybe (Left 12)
Nothing
>>>
rightToMaybe (Right 12)
Just 12
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () #
Traverse elements with access to the index i
, discarding the results (with the arguments flipped).
ifor_
≡flip
itraverse_
When you don't need access to the index then for_
is more flexible in what it accepts.
for_
a ≡ifor_
a.
const
itoList :: FoldableWithIndex i f => f a -> [(i, a)] #
iwither :: (WitherableWithIndex i t, Applicative f) => (i -> a -> f (Maybe b)) -> t a -> f (t b) #
pattern TODO :: () => HasCallStack => a #
decodeUtf8Lenient :: ByteString -> Text #
Decode a strict ByteString
containing UTF-8 encoded text.
lazyDecodeUtf8Lenient :: ByteString -> Text #
Decode a lazy ByteString
containing UTF-8 encoded text.
Any invalid input bytes will be replaced with the Unicode replacement character U+FFFD.
hoistMaybe :: forall (m :: Type -> Type) b. Applicative m => Maybe b -> MaybeT m b #
Orphan instances
(TypeError ('Text "Forbidden FromJSON ByteString instance") :: Constraint) => FromJSON ByteString # | |
(TypeError ('Text "Forbidden ToJSON ByteString instance") :: Constraint) => ToJSON ByteString # | |
Methods toJSON :: ByteString -> Value # toEncoding :: ByteString -> Encoding # toJSONList :: [ByteString] -> Value # toEncodingList :: [ByteString] -> Encoding # omitField :: ByteString -> Bool # |