plutus-contract-model-1.2.0.0
Safe HaskellNone
LanguageHaskell2010

Plutus.Contract.Test.ContractModel.Interface

Synopsis

Contract models

class (Typeable state, Show state, Show (Action state), Eq (Action state), HasSymbolics (Action state), HasVariables (Action state), HasVariables state, Generic state, forall w s e p. Eq (ContractInstanceKey state w s e p), forall w s e p. Show (ContractInstanceKey state w s e p)) => ContractModel state where Source #

A ContractModel instance captures everything that is needed to generate and run tests of a contract or set of contracts. It specifies among other things

Associated Types

data Action state Source #

The type of actions that are supported by the contract. An action usually represents a single callEndpoint or a transfer of tokens, but it can be anything that can be interpreted in the EmulatorTrace monad.

data ContractInstanceKey state :: * -> Row * -> * -> * -> * Source #

To be able to call a contract endpoint from a wallet a ContractHandle is required. These are managed by the test framework and all the user needs to do is provide this contract instance key type representing the different contract instances that a test needs to work with, and when creating a property (see propRunActions_) provide a list of contract instance keys together with their wallets and contracts (a ContractInstanceSpec). Contract instance keys are indexed by the observable state, schema, and error type of the contract and should be defined as a GADT. For example, a handle type for a contract with one seller and multiple buyers could look like this.

 data ContractInstanceKey MyModel w s e where
     Buyer  :: Wallet -> ContractInstanceKey MyModel MyObsState MySchema MyError MyParams
     Seller :: ContractInstanceKey MyModel MyObsState MySchema MyError MyParams

Methods

instanceWallet :: ContractInstanceKey state w s e p -> Wallet Source #

Get the wallet that the contract running at a specific ContractInstanceKey should run in

instanceTag :: forall w s e p. SchemaConstraints w s e => ContractInstanceKey state w s e p -> ContractInstanceTag Source #

The ContractInstanceTag of an instance key for a wallet. Defaults to walletInstanceTag. You must override this if you have multiple instances per wallet.

arbitraryAction :: ModelState state -> Gen (Action state) Source #

Given the current model state, provide a QuickCheck generator for a random next action. This is used in the Arbitrary instance for Actionss as well as by anyAction and anyActions.

actionName :: Action state -> String Source #

The name of an Action, used to report statistics.

waitProbability :: ModelState state -> Double Source #

The probability that we will generate a WaitUntil in a given state

arbitraryWaitInterval :: ModelState state -> Gen Slot Source #

Control the distribution of how long WaitUntil waits

initialState :: state Source #

The initial state, before any actions have been performed.

initialInstances :: [StartContract state] Source #

The initial handles

precondition :: ModelState state -> Action state -> Bool Source #

The precondition function decides if a given action is valid in a given state. Typically actions generated by arbitraryAction will satisfy the precondition, but if they don't they will be discarded and another action will be generated. More importantly, the preconditions are used when shrinking (see shrinkAction) to ensure that shrunk test cases still make sense.

If an explicit action in a DL scenario violates the precondition an error is raised.

nextReactiveState :: Slot -> Spec state () Source #

nextReactiveState is run every time the model waits for a slot to be reached. This can be used to model reactive components of off-chain code.

nextState :: Action state -> Spec state () Source #

This is where the model logic is defined. Given an action, nextState specifies the effects running that action has on the model state. It runs in the Spec monad, which is a state monad over the ModelState.

startInstances :: ModelState state -> Action state -> [StartContract state] Source #

Start new contract instances

instanceContract :: (forall t. HasSymbolicRep t => Symbolic t -> t) -> ContractInstanceKey state w s e p -> p -> Contract w s e () Source #

Map a ContractInstanceKey k to the Contract that is started when we start k in a given ModelState with a given semantics of SymTokens

perform Source #

Arguments

:: HandleFun state

Function from ContractInstanceKey to ContractHandle

-> (forall t. HasSymbolicRep t => Symbolic t -> t)

Map from symbolic things (that may appear in actions or the state) to actual things that appear at runtime

-> ModelState state

The model state before peforming the action

-> Action state

The action to perform

-> SpecificationEmulatorTrace () 

While nextState models the behaviour of the actions, perform contains the code for running the actions in the emulator (see Plutus.Trace.Emulator). It gets access to the wallet contract handles, the current model state, and the action to be performed.

shrinkAction :: ModelState state -> Action state -> [Action state] Source #

When a test involving random sequences of actions fails, the framework tries to find a minimal failing test case by shrinking the original failure. Action sequences are shrunk by removing individual actions, or by replacing an action by one of the (simpler) actions returned by shrinkAction.

See shrink for more information on shrinking.

monitoring Source #

Arguments

:: (ModelState state, ModelState state)

Model state before and after the action

-> Action state

The action that was performed

-> Property 
-> Property 

The monitoring function allows you to collect statistics of your testing using QuickCheck functions like label, collect, classify, and tabulate. This function is called by propRunActions (and friends) for any actions in the given Actions.

Statistics on which actions are executed are always collected.

restricted :: Action state -> Bool Source #

In some scenarios it's useful to have actions that are never generated randomly, but only used explicitly in DL scenario actions. To avoid these actions matching an anyAction when shrinking, they can be marked restricted.

Instances

Instances details
(Typeable state, CrashTolerance state) => ContractModel (WithCrashTolerance state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.CrashTolerance

Associated Types

data Action (WithCrashTolerance state) Source #

data ContractInstanceKey (WithCrashTolerance state) :: Type -> Row Type -> Type -> Type -> Type Source #

Methods

instanceWallet :: forall w (s :: Row Type) e p. ContractInstanceKey (WithCrashTolerance state) w s e p -> Wallet Source #

instanceTag :: forall w (s :: Row Type) e p. SchemaConstraints w s e => ContractInstanceKey (WithCrashTolerance state) w s e p -> ContractInstanceTag Source #

arbitraryAction :: ModelState (WithCrashTolerance state) -> Gen (Action (WithCrashTolerance state)) Source #

actionName :: Action (WithCrashTolerance state) -> String Source #

waitProbability :: ModelState (WithCrashTolerance state) -> Double Source #

arbitraryWaitInterval :: ModelState (WithCrashTolerance state) -> Gen Slot Source #

initialState :: WithCrashTolerance state Source #

initialInstances :: [StartContract (WithCrashTolerance state)] Source #

precondition :: ModelState (WithCrashTolerance state) -> Action (WithCrashTolerance state) -> Bool Source #

nextReactiveState :: Slot -> Spec (WithCrashTolerance state) () Source #

nextState :: Action (WithCrashTolerance state) -> Spec (WithCrashTolerance state) () Source #

startInstances :: ModelState (WithCrashTolerance state) -> Action (WithCrashTolerance state) -> [StartContract (WithCrashTolerance state)] Source #

instanceContract :: forall w (s :: Row Type) e p. (forall t. HasSymbolicRep t => Symbolic t -> t) -> ContractInstanceKey (WithCrashTolerance state) w s e p -> p -> Contract w s e () Source #

perform :: HandleFun (WithCrashTolerance state) -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> ModelState (WithCrashTolerance state) -> Action (WithCrashTolerance state) -> SpecificationEmulatorTrace () Source #

shrinkAction :: ModelState (WithCrashTolerance state) -> Action (WithCrashTolerance state) -> [Action (WithCrashTolerance state)] Source #

monitoring :: (ModelState (WithCrashTolerance state), ModelState (WithCrashTolerance state)) -> Action (WithCrashTolerance state) -> Property -> Property Source #

restricted :: Action (WithCrashTolerance state) -> Bool Source #

type Actions state = Actions (WithInstances (WrappedState state)) Source #

class HasSymbolics a where #

Minimal complete definition

Nothing

Methods

getAllSymbolics :: a -> SymCollectionIndex #

Instances

Instances details
HasSymbolics Char 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Char -> SymCollectionIndex #

HasSymbolics Int 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Int -> SymCollectionIndex #

HasSymbolics Integer 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Integer -> SymCollectionIndex #

(Generic a, GenericHasSymbolics (Rep a)) => HasSymbolics a 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: a -> SymCollectionIndex #

HasSymbolics Wallet Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

getAllSymbolics :: Wallet -> SymCollectionIndex #

HasSymbolics Value 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Value -> SymCollectionIndex #

HasSymbolics Value Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

getAllSymbolics :: Value -> SymCollectionIndex #

HasSymbolics Quantity 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Quantity -> SymCollectionIndex #

HasSymbolics BuiltinByteString Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

getAllSymbolics :: BuiltinByteString -> SymCollectionIndex #

HasSymbolics (Action s) => HasSymbolics (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Methods

getAllSymbolics :: Action (WithInstances s) -> SymCollectionIndex #

HasSymbolics (BaseType a) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: BaseType a -> SymCollectionIndex #

ContractModel state => HasSymbolics (Action (WithCrashTolerance state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.CrashTolerance

Methods

getAllSymbolics :: Action (WithCrashTolerance state) -> SymCollectionIndex #

(HasSymbolics k, HasSymbolics v) => HasSymbolics (Map k v) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Map k v -> SymCollectionIndex #

HasSymbolicRep t => HasSymbolics (Symbolic t) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

Methods

getAllSymbolics :: Symbolic t -> SymCollectionIndex #

Model state

data ModelState state #

Instances

Instances details
Functor ModelState 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

fmap :: (a -> b) -> ModelState a -> ModelState b Source #

(<$) :: a -> ModelState b -> ModelState a Source #

(ContractModel state, Typeable a) => ActionLike state (Action (ModelState state) a) 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

Methods

action :: Action (ModelState state) a -> DL state ()

Show state => Show (ModelState state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

showsPrec :: Int -> ModelState state -> ShowS Source #

show :: ModelState state -> String Source #

showList :: [ModelState state] -> ShowS Source #

Generic (ModelState state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type Rep (ModelState state) :: Type -> Type Source #

Methods

from :: ModelState state -> Rep (ModelState state) x Source #

to :: Rep (ModelState state) x -> ModelState state Source #

(IsRunnable m, RunModel state m) => RunModel (ModelState state) (RunMonad m) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal

Methods

perform :: Typeable a => ModelState state -> Action (ModelState state) a -> LookUp (RunMonad m) -> RunMonad m (Realized (RunMonad m) a)

postcondition :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> PostconditionM (RunMonad m) Bool

monitoring :: (ModelState state, ModelState state) -> Action (ModelState state) a -> LookUp (RunMonad m) -> Realized (RunMonad m) a -> Property -> Property

type Rep (ModelState state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

type Rep (ModelState state) = D1 ('MetaData "ModelState" "Test.QuickCheck.ContractModel.Internal.Spec" "quickcheck-contractmodel-0.1.4.1-3bqn4RrQanG11zXTiHDaXF" 'False) (C1 ('MetaCons "ModelState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_currentSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "_balanceChanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (AddressInEra Era) SymValue)) :*: S1 ('MetaSel ('Just "_minted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymValue))) :*: ((S1 ('MetaSel ('Just "_symbolics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymCollectionIndex) :*: S1 ('MetaSel ('Just "_assertions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Bool)])) :*: (S1 ('MetaSel ('Just "_assertionsOk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_contractState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 state)))))
type StateType (DL state) 
Instance details

Defined in Test.QuickCheck.ContractModel.DL

type StateType (DL state) = state
data Action (ModelState state) a 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Model

data Action (ModelState state) a where

contractState :: Lens (ModelState state1) (ModelState state2) state1 state2 #

currentSlot :: Getter (ModelState state) Slot Source #

balanceChanges :: Getter (ModelState state) (Map (AddressInEra Era) SymValue) #

balanceChange :: Wallet -> Getter (ModelState state) SymValue Source #

minted :: Getter (ModelState state) SymValue #

lockedValue :: ModelState s -> SymValue #

symIsZero :: SymValue -> Bool #

class Monad m => GetModelState (m :: Type -> Type) #

Minimal complete definition

getModelState

Instances

Instances details
GetModelState (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type StateType (Spec state)

Methods

getModelState :: Spec state (ModelState (StateType (Spec state)))

viewModelState :: GetModelState m => Getting a (ModelState (StateType m)) a -> m a #

viewContractState :: (Coercible (StateType m) state, GetModelState m) => Getting a state a -> m a Source #

Get a component of the contract state using a lens.

type SymToken = Symbolic AssetId #

class SymValueLike v where #

Methods

toSymValue :: v -> SymValue #

Instances

Instances details
SymValueLike Value 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

toSymValue :: Value -> SymValue #

SymValueLike Ada Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

toSymValue :: Ada -> SymValue #

SymValueLike Value Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

toSymValue :: Value -> SymValue #

SymValueLike SymValue 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

toSymValue :: SymValue -> SymValue #

class TokenLike t where #

Methods

symAssetIdValueOf :: SymValue -> t -> Quantity #

symAssetIdValue :: t -> Quantity -> SymValue #

Instances

Instances details
TokenLike AssetId 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symAssetIdValueOf :: SymValue -> AssetId -> Quantity #

symAssetIdValue :: AssetId -> Quantity -> SymValue #

TokenLike SymToken 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Methods

symAssetIdValueOf :: SymValue -> SymToken -> Quantity #

symAssetIdValue :: SymToken -> Quantity -> SymValue #

TokenLike AssetClass Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

symAssetIdValueOf :: SymValue -> AssetClass -> Quantity #

symAssetIdValue :: AssetClass -> Quantity -> SymValue #

invSymValue :: SymValue -> SymValue Source #

toValue :: (SymToken -> AssetId) -> SymValue -> Value #

The Spec monad

newtype Spec state a #

Constructors

Spec 

Fields

  • unSpec :: WriterT SymCreationIndex (ReaderT (Var SymIndex) (State (ModelState state))) a
     

Instances

Instances details
MonadState state (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

get :: Spec state state

put :: state -> Spec state ()

state :: (state -> (a, state)) -> Spec state a

Monad (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

(>>=) :: Spec state a -> (a -> Spec state b) -> Spec state b Source #

(>>) :: Spec state a -> Spec state b -> Spec state b Source #

return :: a -> Spec state a Source #

Functor (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

fmap :: (a -> b) -> Spec state a -> Spec state b Source #

(<$) :: a -> Spec state b -> Spec state a Source #

Applicative (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Methods

pure :: a -> Spec state a Source #

(<*>) :: Spec state (a -> b) -> Spec state a -> Spec state b Source #

liftA2 :: (a -> b -> c) -> Spec state a -> Spec state b -> Spec state c Source #

(*>) :: Spec state a -> Spec state b -> Spec state b Source #

(<*) :: Spec state a -> Spec state b -> Spec state a Source #

GetModelState (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type StateType (Spec state)

Methods

getModelState :: Spec state (ModelState (StateType (Spec state)))

type StateType (Spec state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

type StateType (Spec state) = state

wait :: forall state. ContractModel state => Integer -> Spec state () Source #

waitUntil :: forall state. ContractModel state => Slot -> Spec state () Source #

mint :: SymValueLike v => v -> Spec state () #

burn :: SymValueLike v => v -> Spec state () #

deposit :: SymValueLike v => Wallet -> v -> Spec state () Source #

Add tokens to the balanceChange of a wallet. The added tokens are subtracted from the lockedValue of tokens held by contracts.

withdraw :: SymValueLike v => Wallet -> v -> Spec state () Source #

Withdraw tokens from a wallet. The withdrawn tokens are added to the lockedValue of tokens held by contracts.

transfer Source #

Arguments

:: SymValueLike v 
=> Wallet

Transfer from this wallet

-> Wallet

to this wallet

-> v

this many tokens

-> Spec state () 

Transfer tokens between wallets, updating their balances.

createTxOut :: String -> Spec state SymTxOut #

createTxIn :: String -> Spec state SymTxIn #

createSymbolic :: HasSymbolicRep t => String -> Spec state (Symbolic t) #

assertSpec :: String -> Bool -> Spec state () #

type SpecificationEmulatorTrace = Eff (Writer [(String, SomethingWithSymbolicRep)] ': BaseEmulatorEffects) Source #

registerToken :: String -> AssetId -> SpecificationEmulatorTrace () Source #

Register the real token corresponding to a symbolic token created in createToken.

registerTxOut :: String -> TxOut CtxUTxO Era -> SpecificationEmulatorTrace () Source #

Register the real TxOut corresponding to a symbolic TxOut created in createTxOut.

registerTxIn :: String -> TxIn -> SpecificationEmulatorTrace () Source #

Register the real TxIn corresponding to a symbolic TxIn created in createTxIn.

registerSymbolic :: HasSymbolicRep t => String -> t -> SpecificationEmulatorTrace () Source #

delay :: Integer -> SpecificationEmulatorTrace () Source #

`delay n` delays emulator execution by n slots

fromSlotNo :: SlotNo -> Slot Source #

toSlotNo :: Slot -> SlotNo Source #

Test scenarios

type DL state = DL (WithInstances (WrappedState state)) Source #

action :: ContractModel state => Action state -> DL state () Source #

waitUntilDL :: ContractModel state => Slot -> DL state () Source #

observe :: ContractModel state => String -> ((forall t. HasSymbolicRep t => Symbolic t -> t) -> ChainState -> Bool) -> DL state () #

anyAction :: DL state () #

anyActions :: Int -> DL state () #

anyActions_ :: DL state () #

forAllQ :: Quantifiable q => q -> DL s (Quantifies q) #

elementsQ :: Eq a => [a] -> Quantification a #

chooseQ :: (Arbitrary a, Random a, Ord a) => (a, a) -> Quantification a #

Failures

assert :: String -> Bool -> DL s () #

assertModel :: String -> (ModelState state -> Bool) -> DL state () Source #

stopping :: DL state () #

weight :: Double -> DL state () #

getSize :: DL state Int #

monitor :: (Property -> Property) -> DL state () #

Properties

Wallet contract handles

type SchemaConstraints w schema err = (Typeable w, Monoid w, ToJSON w, Typeable schema, ContractConstraints schema, Show err, Typeable err, ToJSON err, FromJSON err, ToJSON w, FromJSON w) Source #

The constraints required on contract schemas and error types to enable calling contract endpoints (callEndpoint).

data StartContract state where Source #

Constructors

StartContract :: (SchemaConstraints w s e, Typeable p) => ContractInstanceKey state w s e p -> p -> StartContract state 

type HandleFun state = forall w schema err params. (Typeable w, Typeable schema, Typeable err, Typeable params) => ContractInstanceKey state w schema err params -> ContractHandle w schema err Source #

A function returning the ContractHandle corresponding to a ContractInstanceKey. A HandleFun is provided to the perform function to enable calling contract endpoints with callEndpoint.

Model properties

propSanityCheckModel :: forall state. ContractModel state => Property Source #

Sanity check a ContractModel. Ensures that wallet balances are not always unchanged.

propSanityCheckAssertions :: forall state. ContractModel state => Actions state -> Property Source #

Sanity check a ContractModel. Ensures that all assertions in the property generation succeed.

propSanityCheckReactive :: forall state. (ContractModel state, Eq state) => Actions state -> Positive Integer -> Positive Integer -> Property Source #

Sanity check a ContractModel. Ensures that nextReactiveState is idempotent.

Coverage checking options

data CoverageOptions Source #

Options for controlling coverage checking requirements

  • checkCoverage tells you whether or not to run the coverage checks at all.
  • `endpointCoverageEq instance endpointName` tells us what percentage of tests are required to include a call to the endpoint endpointName in the contract at `instance`.
  • coverIndex is the coverage index obtained from the CompiledCodeIn of the validator.

defaultCoverageOptions :: CoverageOptions Source #

Default coverage checking options are: * not to check coverage * set the requriements for every endpoint to 20% and * not to cover any source locations in the validator scripts.

endpointCoverageReq :: Lens' CoverageOptions (ContractInstanceTag -> String -> Double) Source #

coverageIndex :: Lens' CoverageOptions CoverageIndex Source #

quickCheckWithCoverage :: Testable prop => Args -> CoverageOptions -> (CoverageOptions -> prop) -> IO CoverageReport Source #

Run QuickCheck on a property that tracks coverage and print its coverage report.

quickCheckWithCoverageAndResult :: Testable prop => Args -> CoverageOptions -> (CoverageOptions -> prop) -> IO (CoverageReport, Result) Source #

Emulator properties

propRunActions_ Source #

Arguments

:: ContractModel state 
=> Actions state

The actions to run

-> Property 

Run a Actions in the emulator and check that the model and the emulator agree on the final wallet balance changes. Equivalent to

propRunActions_ hs actions = propRunActions hs (const $ pure True) actions

propRunActions Source #

Arguments

:: ContractModel state 
=> (ModelState state -> TracePredicate)

Predicate to check at the end

-> Actions state

The actions to run

-> Property 

Run a Actions in the emulator and check that the model and the emulator agree on the final wallet balance changes, and that the given TracePredicate holds at the end. Equivalent to:

propRunActions = propRunActionsWithOptions defaultCheckOptionsContractModel defaultCoverageOptions

propRunActionsWithOptions Source #

Arguments

:: ContractModel state 
=> CheckOptions

Emulator options

-> CoverageOptions

Coverage options

-> (ModelState state -> TracePredicate)

Predicate to check at the end

-> Actions state

The actions to run

-> Property 

Run a Actions in the emulator and check that the model and the emulator agree on the final wallet balance changes, that no off-chain contract instance crashed, and that the given TracePredicate holds at the end. The predicate has access to the final model state.

The Actions argument can be generated by a forAllDL from a DL scenario, or using the Arbitrary instance for actions which generates random actions using arbitraryAction:

>>> quickCheck $ propRunActions_ handles
+++ OK, passed 100 tests
>>> quickCheck $ forAllDL dl $ propRunActions_ handles
+++ OK, passed 100 tests

The options argument can be used to configure the emulator--setting initial wallet balances, the maximum number of slots to run for, and the log level for the emulator trace printed on failing tests:

options :: Map Wallet Value -> Slot -> LogLevel -> CheckOptions
options dist slot logLevel =
    defaultCheckOptions & emulatorConfig . initialChainState .~ Left dist
                          & minLogLevel                        .~ logLevel

defaultCheckOptionsContractModel :: CheckOptions Source #

Default check options that include a large amount of Ada in the initial distributions to avoid having to write ContractModels that keep track of balances.

checkThreatModel Source #

Arguments

:: CheckableContractModel state 
=> ThreatModel a 
-> Actions (WithInstances state)

The actions to run

-> Property 

Check a threat model on all transactions produced by the given actions.

checkThreatModelWithOptions Source #

Arguments

:: CheckableContractModel state 
=> CheckOptions

Emulator options

-> CoverageOptions

Coverage options

-> ThreatModel a 
-> Actions (WithInstances state)

The actions to run

-> Property 

Check a threat model on all transactions produced by the given actions.

DL properties

forAllDL :: (ContractModel state, Testable p) => DL state () -> (Actions state -> p) -> Property #

Standard properties

pattern NoLockedFundsProof :: DL (WithInstances model) () -> (Wallet -> DL (WithInstances model) ()) -> (ModelState (WithInstances model) -> SymValue) -> (ModelState (WithInstances model) -> SymValue) -> NoLockedFundsProof model Source #

nlfpMainStrategy :: NoLockedFundsProof model -> DL (WithInstances model) () Source #

Strategy to recover all funds from the contract in any reachable state.

nlfpWalletStrategy :: NoLockedFundsProof model -> Wallet -> DL (WithInstances model) () Source #

A strategy for each wallet to recover as much (or more) funds as the main strategy would give them in a given state, without the assistance of any other wallet.

nlfpOverhead :: NoLockedFundsProof model -> ModelState (WithInstances model) -> SymValue Source #

An initial amount of overhead value that may be lost - e.g. setup fees for scripts that can't be recovered.

nlfpErrorMargin :: NoLockedFundsProof model -> ModelState (WithInstances model) -> SymValue Source #

The total amount of margin for error in the value collected by the WalletStrategy compared to the MainStrategy. This is useful if your contract contains rounding code that makes the order of operations have a small but predictable effect on the value collected by different wallets.

defaultNLFP :: NoLockedFundsProof model Source #

The default skeleton of a NoLockedFundsProof - doesn't permit any overhead or error margin.

checkNoLockedFundsProof :: CheckableContractModel model => NoLockedFundsProof model -> Property Source #

Check a NoLockedFundsProof. Each test will generate an arbitrary sequence of actions (anyActions_) and ask the nlfpMainStrategy to recover all funds locked by the contract after performing those actions. This results in some distribution of the contract funds to the wallets, and the test then asks each nlfpWalletStrategy to show how to recover their allotment of funds without any assistance from the other wallets (assuming the main strategy did not execute). When executing wallet strategies, the off-chain instances for other wallets are killed and their private keys are deleted from the emulator state.

data Whitelist Source #

A whitelist entry tells you what final log entry prefixes are acceptable for a given error

whitelistOk :: Whitelist -> Bool Source #

Check that a whitelist does not accept any partial functions

checkErrorWhitelist :: ContractModel m => Whitelist -> Actions m -> Property Source #

Check that running a contract model does not result in validation failures that are not accepted by the whitelist.

checkErrorWhitelistWithOptions :: forall m. ContractModel m => CheckOptions -> CoverageOptions -> Whitelist -> Actions m -> Property Source #

Check that running a contract model does not result in validation failures that are not accepted by the whitelist.

newtype WithInstances s Source #

Constructors

WithInstances 

Fields

Instances

Instances details
Eq (Action s) => Eq (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Methods

(==) :: Action (WithInstances s) -> Action (WithInstances s) -> Bool Source #

(/=) :: Action (WithInstances s) -> Action (WithInstances s) -> Bool Source #

Eq s => Eq (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Show (Action s) => Show (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Methods

showsPrec :: Int -> Action (WithInstances s) -> ShowS Source #

show :: Action (WithInstances s) -> String Source #

showList :: [Action (WithInstances s)] -> ShowS Source #

Show s => Show (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Generic (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Associated Types

type Rep (Action (WithInstances s)) :: Type -> Type Source #

Methods

from :: Action (WithInstances s) -> Rep (Action (WithInstances s)) x Source #

to :: Rep (Action (WithInstances s)) x -> Action (WithInstances s) Source #

Generic (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Associated Types

type Rep (WithInstances s) :: Type -> Type Source #

ContractModel s => ContractModel (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Associated Types

data Action (WithInstances s)

HasSymbolics (Action s) => HasSymbolics (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Methods

getAllSymbolics :: Action (WithInstances s) -> SymCollectionIndex #

CheckableContractModel state => RunModel (WithInstances state) (EmulatorTraceWithInstances state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Methods

perform :: ModelState (WithInstances state) -> Action (WithInstances state) -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> RunMonad (EmulatorTraceWithInstances state) ()

monitoring :: (ModelState (WithInstances state), ModelState (WithInstances state)) -> Action (WithInstances state) -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> SymIndex -> Property -> Property

type Rep (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

type Rep (Action (WithInstances s)) = D1 ('MetaData "Action" "Plutus.Contract.Test.ContractModel.Internal" "plutus-contract-model-1.2.0.0-AT5Aekx0s4LCgIL1y0MF95" 'False) (C1 ('MetaCons "UnderlyingAction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Action s))) :+: C1 ('MetaCons "Unilateral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Wallet)))
type Rep (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

type Rep (WithInstances s) = D1 ('MetaData "WithInstances" "Plutus.Contract.Test.ContractModel.Internal" "plutus-contract-model-1.2.0.0-AT5Aekx0s4LCgIL1y0MF95" 'True) (C1 ('MetaCons "WithInstances" 'PrefixI 'True) (S1 ('MetaSel ('Just "withoutInstances") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s)))
data Action (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

data Action (WithInstances s)

newtype WrappedState state Source #

Constructors

WrapState 

Fields

Instances

Instances details
Eq (Action state) => Eq (Action (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

(==) :: Action (WrappedState state) -> Action (WrappedState state) -> Bool Source #

(/=) :: Action (WrappedState state) -> Action (WrappedState state) -> Bool Source #

Eq state => Eq (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

(==) :: WrappedState state -> WrappedState state -> Bool Source #

(/=) :: WrappedState state -> WrappedState state -> Bool Source #

Ord state => Ord (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

compare :: WrappedState state -> WrappedState state -> Ordering Source #

(<) :: WrappedState state -> WrappedState state -> Bool Source #

(<=) :: WrappedState state -> WrappedState state -> Bool Source #

(>) :: WrappedState state -> WrappedState state -> Bool Source #

(>=) :: WrappedState state -> WrappedState state -> Bool Source #

max :: WrappedState state -> WrappedState state -> WrappedState state Source #

min :: WrappedState state -> WrappedState state -> WrappedState state Source #

Show (Action state) => Show (Action (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

showsPrec :: Int -> Action (WrappedState state) -> ShowS Source #

show :: Action (WrappedState state) -> String Source #

showList :: [Action (WrappedState state)] -> ShowS Source #

Show state => Show (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Generic (Action (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

type Rep (Action (WrappedState state)) :: Type -> Type Source #

Methods

from :: Action (WrappedState state) -> Rep (Action (WrappedState state)) x Source #

to :: Rep (Action (WrappedState state)) x -> Action (WrappedState state) Source #

Generic (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

type Rep (WrappedState state) :: Type -> Type Source #

Methods

from :: WrappedState state -> Rep (WrappedState state) x Source #

to :: Rep (WrappedState state) x -> WrappedState state Source #

ContractModel state => ContractModel (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

data Action (WrappedState state)

Methods

arbitraryAction :: ModelState (WrappedState state) -> Gen (Action (WrappedState state))

actionName :: Action (WrappedState state) -> String

waitProbability :: ModelState (WrappedState state) -> Double

arbitraryWaitInterval :: ModelState (WrappedState state) -> Gen SlotNo

initialState :: WrappedState state

precondition :: ModelState (WrappedState state) -> Action (WrappedState state) -> Bool

nextReactiveState :: SlotNo -> Spec (WrappedState state) ()

nextState :: Action (WrappedState state) -> Spec (WrappedState state) ()

shrinkAction :: ModelState (WrappedState state) -> Action (WrappedState state) -> [Action (WrappedState state)]

restricted :: Action (WrappedState state) -> Bool

ContractModel state => ContractInstanceModel (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

data ContractInstanceKey (WrappedState state) :: Type -> Row Type -> Type -> Type -> Type Source #

Methods

instanceWallet :: forall w (s :: Row Type) e p. ContractInstanceKey (WrappedState state) w s e p -> Wallet Source #

instanceTag :: forall w (s :: Row Type) e p. SchemaConstraints w s e => ContractInstanceKey (WrappedState state) w s e p -> ContractInstanceTag Source #

initialInstances :: [StartContract (WrappedState state)] Source #

startInstances :: ModelState (WrappedState state) -> Action (WrappedState state) -> [StartContract (WrappedState state)] Source #

instanceContract :: forall w (s :: Row Type) e p. (forall t. HasSymbolicRep t => Symbolic t -> t) -> ContractInstanceKey (WrappedState state) w s e p -> p -> Contract w s e () Source #

ContractModel state => RunModel (WrappedState state) (SpecificationEmulatorTrace (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

perform :: ModelState (WrappedState state) -> Action (WrappedState state) -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> RunMonad (SpecificationEmulatorTrace (WrappedState state)) ()

monitoring :: (ModelState (WrappedState state), ModelState (WrappedState state)) -> Action (WrappedState state) -> (forall t. HasSymbolicRep t => Symbolic t -> t) -> SymIndex -> Property -> Property

Eq (ContractInstanceKey state w s e p) => Eq (ContractInstanceKey (WrappedState state) w s e p) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Methods

(==) :: ContractInstanceKey (WrappedState state) w s e p -> ContractInstanceKey (WrappedState state) w s e p -> Bool Source #

(/=) :: ContractInstanceKey (WrappedState state) w s e p -> ContractInstanceKey (WrappedState state) w s e p -> Bool Source #

Show (ContractInstanceKey state w s e p) => Show (ContractInstanceKey (WrappedState state) w s e p) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

type Rep (Action (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

type Rep (Action (WrappedState state)) = D1 ('MetaData "Action" "Plutus.Contract.Test.ContractModel.Interface" "plutus-contract-model-1.2.0.0-AT5Aekx0s4LCgIL1y0MF95" 'True) (C1 ('MetaCons "WrapAction" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapAction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Action state))))
type Rep (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

type Rep (WrappedState state) = D1 ('MetaData "WrappedState" "Plutus.Contract.Test.ContractModel.Interface" "plutus-contract-model-1.2.0.0-AT5Aekx0s4LCgIL1y0MF95" 'True) (C1 ('MetaCons "WrapState" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 state)))
newtype Action (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

newtype Action (WrappedState state) = WrapAction {}
newtype ContractInstanceKey (WrappedState state) w s e p Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

checkDoubleSatisfaction :: forall m. ContractModel m => Actions m -> Property Source #

Perform a light-weight check to find egregious double satisfaction vulnerabilities in contracts.

A counterexample to this property consists of three transactions. * The first transaction is a valid transaction from the trace generated by the contract model. * The second transaction, generated by redirecting a non-datum pubkey output from a non-signer to a signer in the first transaction, fails to validate. This demonstrates that funds can't simply be stolen. * The third transaction goes through and manages to steal funds by altering the first transaction. It is generated by adding another script input (with the same value as the non-signer non-stealable pubkey output) and adding a datum to the non-signer non-stealable pubkey output, and giving the extra value from the new script input to a signer.

checkDoubleSatisfactionWithOptions :: forall m. ContractModel m => CheckOptions -> CoverageOptions -> Actions m -> Property Source #

Perform a light-weight check to find egregious double satisfaction vulnerabilities in contracts, with options.

class Generic a Source #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type Source #

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type Source #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type Source #

Methods

from :: Exp -> Rep Exp x Source #

to :: Rep Exp x -> Exp Source #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type Source #

Methods

from :: Match -> Rep Match x Source #

to :: Rep Match x -> Match Source #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type Source #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type Source #

Methods

from :: Pat -> Rep Pat x Source #

to :: Rep Pat x -> Pat Source #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type Source #

Methods

from :: Type -> Rep Type x Source #

to :: Rep Type x -> Type Source #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type Source #

Methods

from :: Dec -> Rep Dec x Source #

to :: Rep Dec x -> Dec Source #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type Source #

Methods

from :: Name -> Rep Name x Source #

to :: Rep Name x -> Name Source #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type Source #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type Source #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type Source #

Generic ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type Source #

Methods

from :: () -> Rep () x Source #

to :: Rep () x -> () Source #

Generic Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type Source #

Methods

from :: Void -> Rep Void x Source #

to :: Rep Void x -> Void Source #

Generic Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type Source #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type Source #

Generic All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type Source #

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Generic Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type Source #

Generic SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type Source #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type Source #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type Source #

Methods

from :: Doc -> Rep Doc x Source #

to :: Rep Doc x -> Doc Source #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type Source #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type Source #

Methods

from :: Mode -> Rep Mode x Source #

to :: Rep Mode x -> Mode Source #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type Source #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type Source #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type Source #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type Source #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type Source #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type Source #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type Source #

Methods

from :: Loc -> Rep Loc x Source #

to :: Rep Loc x -> Loc Source #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type Source #

Methods

from :: Info -> Rep Info x Source #

to :: Rep Info x -> Info Source #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type Source #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type Source #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type Source #

Methods

from :: Lit -> Rep Lit x Source #

to :: Rep Lit x -> Lit Source #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type Source #

Methods

from :: Bytes -> Rep Bytes x Source #

to :: Rep Bytes x -> Bytes Source #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type Source #

Methods

from :: Body -> Rep Body x Source #

to :: Rep Body x -> Body Source #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type Source #

Methods

from :: Guard -> Rep Guard x Source #

to :: Rep Guard x -> Guard Source #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type Source #

Methods

from :: Stmt -> Rep Stmt x Source #

to :: Rep Stmt x -> Stmt Source #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type Source #

Methods

from :: Range -> Rep Range x Source #

to :: Rep Range x -> Range Source #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type Source #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type Source #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type Source #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type Source #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type Source #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type Source #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type Source #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type Source #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type Source #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type Source #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type Source #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type Source #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type Source #

Methods

from :: Con -> Rep Con x Source #

to :: Rep Con x -> Con Source #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type Source #

Methods

from :: Bang -> Rep Bang x Source #

to :: Rep Bang x -> Bang Source #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type Source #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type Source #

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: Type -> Type Source #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type Source #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type Source #

Methods

from :: TyLit -> Rep TyLit x Source #

to :: Rep TyLit x -> TyLit Source #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type Source #

Methods

from :: Role -> Rep Role x Source #

to :: Rep Role x -> Role Source #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type Source #

Generic ContractInstanceLog 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep ContractInstanceLog :: Type -> Type Source #

Methods

from :: ContractInstanceLog -> Rep ContractInstanceLog x Source #

to :: Rep ContractInstanceLog x -> ContractInstanceLog Source #

Generic ContractInstanceMsg 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep ContractInstanceMsg :: Type -> Type Source #

Methods

from :: ContractInstanceMsg -> Rep ContractInstanceMsg x Source #

to :: Rep ContractInstanceMsg x -> ContractInstanceMsg Source #

Generic ContractInstanceTag 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep ContractInstanceTag :: Type -> Type Source #

Methods

from :: ContractInstanceTag -> Rep ContractInstanceTag x Source #

to :: Rep ContractInstanceTag x -> ContractInstanceTag Source #

Generic EmulatorRuntimeError 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep EmulatorRuntimeError :: Type -> Type Source #

Methods

from :: EmulatorRuntimeError -> Rep EmulatorRuntimeError x Source #

to :: Rep EmulatorRuntimeError x -> EmulatorRuntimeError Source #

Generic UserThreadMsg 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep UserThreadMsg :: Type -> Type Source #

Methods

from :: UserThreadMsg -> Rep UserThreadMsg x Source #

to :: Rep UserThreadMsg x -> UserThreadMsg Source #

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Generic OnChainTx 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep OnChainTx :: Type -> Type Source #

Methods

from :: OnChainTx -> Rep OnChainTx x Source #

to :: Rep OnChainTx x -> OnChainTx Source #

Generic EndpointDescription 
Instance details

Defined in Wallet.Types

Associated Types

type Rep EndpointDescription :: Type -> Type Source #

Methods

from :: EndpointDescription -> Rep EndpointDescription x Source #

to :: Rep EndpointDescription x -> EndpointDescription Source #

Generic NotificationError 
Instance details

Defined in Wallet.Types

Associated Types

type Rep NotificationError :: Type -> Type Source #

Methods

from :: NotificationError -> Rep NotificationError x Source #

to :: Rep NotificationError x -> NotificationError Source #

Generic Notification 
Instance details

Defined in Wallet.Types

Associated Types

type Rep Notification :: Type -> Type Source #

Methods

from :: Notification -> Rep Notification x Source #

to :: Rep Notification x -> Notification Source #

Generic ThreadId 
Instance details

Defined in Plutus.Trace.Scheduler

Associated Types

type Rep ThreadId :: Type -> Type Source #

Methods

from :: ThreadId -> Rep ThreadId x Source #

to :: Rep ThreadId x -> ThreadId Source #

Generic ContractInstanceId 
Instance details

Defined in Wallet.Types

Associated Types

type Rep ContractInstanceId :: Type -> Type Source #

Methods

from :: ContractInstanceId -> Rep ContractInstanceId x Source #

to :: Rep ContractInstanceId x -> ContractInstanceId Source #

Generic Wallet 
Instance details

Defined in Wallet.Emulator.Wallet

Associated Types

type Rep Wallet :: Type -> Type Source #

Methods

from :: Wallet -> Rep Wallet x Source #

to :: Rep Wallet x -> Wallet Source #

Generic WalletAPIError 
Instance details

Defined in Wallet.Emulator.Error

Associated Types

type Rep WalletAPIError :: Type -> Type Source #

Methods

from :: WalletAPIError -> Rep WalletAPIError x Source #

to :: Rep WalletAPIError x -> WalletAPIError Source #

Generic Ada 
Instance details

Defined in Plutus.Script.Utils.Ada

Associated Types

type Rep Ada :: Type -> Type Source #

Methods

from :: Ada -> Rep Ada x Source #

to :: Rep Ada x -> Ada Source #

Generic PaymentPubKeyHash 
Instance details

Defined in Ledger.Address

Associated Types

type Rep PaymentPubKeyHash :: Type -> Type Source #

Methods

from :: PaymentPubKeyHash -> Rep PaymentPubKeyHash x Source #

to :: Rep PaymentPubKeyHash x -> PaymentPubKeyHash Source #

Generic ValidationError 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationError :: Type -> Type Source #

Methods

from :: ValidationError -> Rep ValidationError x Source #

to :: Rep ValidationError x -> ValidationError Source #

Generic ToCardanoError 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Associated Types

type Rep ToCardanoError :: Type -> Type Source #

Methods

from :: ToCardanoError -> Rep ToCardanoError x Source #

to :: Rep ToCardanoError x -> ToCardanoError Source #

Generic MkTxError 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep MkTxError :: Type -> Type Source #

Methods

from :: MkTxError -> Rep MkTxError x Source #

to :: Rep MkTxError x -> MkTxError Source #

Generic PABResp 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep PABResp :: Type -> Type Source #

Methods

from :: PABResp -> Rep PABResp x Source #

to :: Rep PABResp x -> PABResp Source #

Generic PABReq 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep PABReq :: Type -> Type Source #

Methods

from :: PABReq -> Rep PABReq x Source #

to :: Rep PABReq x -> PABReq Source #

Generic CheckpointKey 
Instance details

Defined in Plutus.Contract.Checkpoint

Associated Types

type Rep CheckpointKey :: Type -> Type Source #

Methods

from :: CheckpointKey -> Rep CheckpointKey x Source #

to :: Rep CheckpointKey x -> CheckpointKey Source #

Generic RequestHandlerLogMsg 
Instance details

Defined in Wallet.Emulator.LogMessages

Associated Types

type Rep RequestHandlerLogMsg :: Type -> Type Source #

Methods

from :: RequestHandlerLogMsg -> Rep RequestHandlerLogMsg x Source #

to :: Rep RequestHandlerLogMsg x -> RequestHandlerLogMsg Source #

Generic TxBalanceMsg 
Instance details

Defined in Cardano.Node.Emulator.LogMessages

Associated Types

type Rep TxBalanceMsg :: Type -> Type Source #

Methods

from :: TxBalanceMsg -> Rep TxBalanceMsg x Source #

to :: Rep TxBalanceMsg x -> TxBalanceMsg Source #

Generic Slot 
Instance details

Defined in Ledger.Slot

Associated Types

type Rep Slot :: Type -> Type Source #

Methods

from :: Slot -> Rep Slot x Source #

to :: Rep Slot x -> Slot Source #

Generic CheckpointError 
Instance details

Defined in Plutus.Contract.Checkpoint

Associated Types

type Rep CheckpointError :: Type -> Type Source #

Methods

from :: CheckpointError -> Rep CheckpointError x Source #

to :: Rep CheckpointError x -> CheckpointError Source #

Generic ContractError 
Instance details

Defined in Plutus.Contract.Error

Associated Types

type Rep ContractError :: Type -> Type Source #

Methods

from :: ContractError -> Rep ContractError x Source #

to :: Rep ContractError x -> ContractError Source #

Generic EndpointError 
Instance details

Defined in Plutus.Contract.Trace

Associated Types

type Rep EndpointError :: Type -> Type Source #

Methods

from :: EndpointError -> Rep EndpointError x Source #

to :: Rep EndpointError x -> EndpointError Source #

Generic EmulatorEvent' 
Instance details

Defined in Wallet.Emulator.MultiAgent

Associated Types

type Rep EmulatorEvent' :: Type -> Type Source #

Methods

from :: EmulatorEvent' -> Rep EmulatorEvent' x Source #

to :: Rep EmulatorEvent' x -> EmulatorEvent' Source #

Generic CoverageData 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CoverageData :: Type -> Type Source #

Methods

from :: CoverageData -> Rep CoverageData x Source #

to :: Rep CoverageData x -> CoverageData Source #

Generic Data 
Instance details

Defined in PlutusCore.Data

Associated Types

type Rep Data :: Type -> Type Source #

Methods

from :: Data -> Rep Data x Source #

to :: Rep Data x -> Data Source #

Generic Params 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.Params

Associated Types

type Rep Params :: Type -> Type Source #

Methods

from :: Params -> Rep Params x Source #

to :: Rep Params x -> Params Source #

Generic LogLevel 
Instance details

Defined in Control.Monad.Freer.Extras.Log

Associated Types

type Rep LogLevel :: Type -> Type Source #

Methods

from :: LogLevel -> Rep LogLevel x Source #

to :: Rep LogLevel x -> LogLevel Source #

Generic WalletId 
Instance details

Defined in Wallet.Emulator.Wallet

Associated Types

type Rep WalletId :: Type -> Type Source #

Methods

from :: WalletId -> Rep WalletId x Source #

to :: Rep WalletId x -> WalletId Source #

Generic TyName 
Instance details

Defined in PlutusCore.Name

Associated Types

type Rep TyName :: Type -> Type Source #

Methods

from :: TyName -> Rep TyName x Source #

to :: Rep TyName x -> TyName Source #

Generic Name 
Instance details

Defined in PlutusCore.Name

Associated Types

type Rep Name :: Type -> Type Source #

Methods

from :: Name -> Rep Name x Source #

to :: Rep Name x -> Name Source #

Generic DefaultFun 
Instance details

Defined in PlutusCore.Default.Builtins

Associated Types

type Rep DefaultFun :: Type -> Type Source #

Methods

from :: DefaultFun -> Rep DefaultFun x Source #

to :: Rep DefaultFun x -> DefaultFun Source #

Generic UnbalancedTx 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep UnbalancedTx :: Type -> Type Source #

Methods

from :: UnbalancedTx -> Rep UnbalancedTx x Source #

to :: Rep UnbalancedTx x -> UnbalancedTx Source #

Generic ChainEvent 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.Chain

Associated Types

type Rep ChainEvent :: Type -> Type Source #

Methods

from :: ChainEvent -> Rep ChainEvent x Source #

to :: Rep ChainEvent x -> ChainEvent Source #

Generic ValidationPhase 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationPhase :: Type -> Type Source #

Methods

from :: ValidationPhase -> Rep ValidationPhase x Source #

to :: Rep ValidationPhase x -> ValidationPhase Source #

Generic Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Generic Validator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Validator :: Type -> Type Source #

Methods

from :: Validator -> Rep Validator x Source #

to :: Rep Validator x -> Validator Source #

Generic DeBruijn 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep DeBruijn :: Type -> Type Source #

Methods

from :: DeBruijn -> Rep DeBruijn x Source #

to :: Rep DeBruijn x -> DeBruijn Source #

Generic SchedulerLog 
Instance details

Defined in Plutus.Trace.Scheduler

Associated Types

type Rep SchedulerLog :: Type -> Type Source #

Methods

from :: SchedulerLog -> Rep SchedulerLog x Source #

to :: Rep SchedulerLog x -> SchedulerLog Source #

Generic SymValue 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep SymValue :: Type -> Type Source #

Methods

from :: SymValue -> Rep SymValue x Source #

to :: Rep SymValue x -> SymValue Source #

Generic HsConstraintDefinition 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsConstraintDefinition :: Type -> Type Source #

Methods

from :: HsConstraintDefinition -> Rep HsConstraintDefinition x Source #

to :: Rep HsConstraintDefinition x -> HsConstraintDefinition Source #

Generic HsDataType 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsDataType :: Type -> Type Source #

Methods

from :: HsDataType -> Rep HsDataType x Source #

to :: Rep HsDataType x -> HsDataType Source #

Generic HsExpr 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsExpr :: Type -> Type Source #

Methods

from :: HsExpr -> Rep HsExpr x Source #

to :: Rep HsExpr x -> HsExpr Source #

Generic HsImport 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsImport :: Type -> Type Source #

Methods

from :: HsImport -> Rep HsImport x Source #

to :: Rep HsImport x -> HsImport Source #

Generic HsNone 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsNone :: Type -> Type Source #

Methods

from :: HsNone -> Rep HsNone x Source #

to :: Rep HsNone x -> HsNone Source #

Generic HsType 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsType :: Type -> Type Source #

Methods

from :: HsType -> Rep HsType x Source #

to :: Rep HsType x -> HsType Source #

Generic Boxed 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Boxed :: Type -> Type Source #

Methods

from :: Boxed -> Rep Boxed x Source #

to :: Rep Boxed x -> Boxed Source #

Generic SrcSpanInfo 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpanInfo :: Type -> Type Source #

Methods

from :: SrcSpanInfo -> Rep SrcSpanInfo x Source #

to :: Rep SrcSpanInfo x -> SrcSpanInfo Source #

Generic SrcLoc 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcLoc :: Type -> Type Source #

Methods

from :: SrcLoc -> Rep SrcLoc x Source #

to :: Rep SrcLoc x -> SrcLoc Source #

Generic SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpan :: Type -> Type Source #

Methods

from :: SrcSpan -> Rep SrcSpan x Source #

to :: Rep SrcSpan x -> SrcSpan Source #

Generic DropName 
Instance details

Defined in Cardano.BM.Data.SubTrace

Associated Types

type Rep DropName :: Type -> Type Source #

Methods

from :: DropName -> Rep DropName x Source #

to :: Rep DropName x -> DropName Source #

Generic NameSelector 
Instance details

Defined in Cardano.BM.Data.SubTrace

Associated Types

type Rep NameSelector :: Type -> Type Source #

Methods

from :: NameSelector -> Rep NameSelector x Source #

to :: Rep NameSelector x -> NameSelector Source #

Generic SubTrace 
Instance details

Defined in Cardano.BM.Data.SubTrace

Associated Types

type Rep SubTrace :: Type -> Type Source #

Methods

from :: SubTrace -> Rep SubTrace x Source #

to :: Rep SubTrace x -> SubTrace Source #

Generic UnhideNames 
Instance details

Defined in Cardano.BM.Data.SubTrace

Associated Types

type Rep UnhideNames :: Type -> Type Source #

Methods

from :: UnhideNames -> Rep UnhideNames x Source #

to :: Rep UnhideNames x -> UnhideNames Source #

Generic ObservableInstance 
Instance details

Defined in Cardano.BM.Data.Observable

Associated Types

type Rep ObservableInstance :: Type -> Type Source #

Methods

from :: ObservableInstance -> Rep ObservableInstance x Source #

to :: Rep ObservableInstance x -> ObservableInstance Source #

Generic Severity 
Instance details

Defined in Cardano.BM.Data.Severity

Associated Types

type Rep Severity :: Type -> Type Source #

Methods

from :: Severity -> Rep Severity x Source #

to :: Rep Severity x -> Severity Source #

Generic IsUtxoResponse 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep IsUtxoResponse :: Type -> Type Source #

Methods

from :: IsUtxoResponse -> Rep IsUtxoResponse x Source #

to :: Rep IsUtxoResponse x -> IsUtxoResponse Source #

Generic QueryAtAddressRequest 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep QueryAtAddressRequest :: Type -> Type Source #

Methods

from :: QueryAtAddressRequest -> Rep QueryAtAddressRequest x Source #

to :: Rep QueryAtAddressRequest x -> QueryAtAddressRequest Source #

Generic TxoAtAddressRequest 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep TxoAtAddressRequest :: Type -> Type Source #

Methods

from :: TxoAtAddressRequest -> Rep TxoAtAddressRequest x Source #

to :: Rep TxoAtAddressRequest x -> TxoAtAddressRequest Source #

Generic TxosResponse 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep TxosResponse :: Type -> Type Source #

Methods

from :: TxosResponse -> Rep TxosResponse x Source #

to :: Rep TxosResponse x -> TxosResponse Source #

Generic UtxoByAddressRequest 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep UtxoByAddressRequest :: Type -> Type Source #

Methods

from :: UtxoByAddressRequest -> Rep UtxoByAddressRequest x Source #

to :: Rep UtxoByAddressRequest x -> UtxoByAddressRequest Source #

Generic UtxoWithCurrencyRequest 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep UtxoWithCurrencyRequest :: Type -> Type Source #

Methods

from :: UtxoWithCurrencyRequest -> Rep UtxoWithCurrencyRequest x Source #

to :: Rep UtxoWithCurrencyRequest x -> UtxoWithCurrencyRequest Source #

Generic UtxosResponse 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep UtxosResponse :: Type -> Type Source #

Methods

from :: UtxosResponse -> Rep UtxosResponse x Source #

to :: Rep UtxosResponse x -> UtxosResponse Source #

Generic TxOutRef 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxOutRef :: Type -> Type Source #

Methods

from :: TxOutRef -> Rep TxOutRef x Source #

to :: Rep TxOutRef x -> TxOutRef Source #

Generic AssetClass 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep AssetClass :: Type -> Type Source #

Methods

from :: AssetClass -> Rep AssetClass x Source #

to :: Rep AssetClass x -> AssetClass Source #

Generic Tip 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Tip :: Type -> Type Source #

Methods

from :: Tip -> Rep Tip x Source #

to :: Rep Tip x -> Tip Source #

Generic CurrencySymbol 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep CurrencySymbol :: Type -> Type Source #

Methods

from :: CurrencySymbol -> Rep CurrencySymbol x Source #

to :: Rep CurrencySymbol x -> CurrencySymbol Source #

Generic TokenName 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep TokenName :: Type -> Type Source #

Methods

from :: TokenName -> Rep TokenName x Source #

to :: Rep TokenName x -> TokenName Source #

Generic Schema 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Schema :: Type -> Type Source #

Methods

from :: Schema -> Rep Schema x Source #

to :: Rep Schema x -> Schema Source #

Generic NamedSchema 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep NamedSchema :: Type -> Type Source #

Methods

from :: NamedSchema -> Rep NamedSchema x Source #

to :: Rep NamedSchema x -> NamedSchema Source #

Generic Credential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Associated Types

type Rep Credential :: Type -> Type Source #

Methods

from :: Credential -> Rep Credential x Source #

to :: Rep Credential x -> Credential Source #

Generic PubKeyHash 
Instance details

Defined in Plutus.V1.Ledger.Crypto

Associated Types

type Rep PubKeyHash :: Type -> Type Source #

Methods

from :: PubKeyHash -> Rep PubKeyHash x Source #

to :: Rep PubKeyHash x -> PubKeyHash Source #

Generic ValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ValidatorHash :: Type -> Type Source #

Methods

from :: ValidatorHash -> Rep ValidatorHash x Source #

to :: Rep ValidatorHash x -> ValidatorHash Source #

Generic DatumFromQuery 
Instance details

Defined in Ledger.Tx

Associated Types

type Rep DatumFromQuery :: Type -> Type Source #

Methods

from :: DatumFromQuery -> Rep DatumFromQuery x Source #

to :: Rep DatumFromQuery x -> DatumFromQuery Source #

Generic Datum 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Datum :: Type -> Type Source #

Methods

from :: Datum -> Rep Datum x Source #

to :: Rep Datum x -> Datum Source #

Generic DecoratedTxOut 
Instance details

Defined in Ledger.Tx

Associated Types

type Rep DecoratedTxOut :: Type -> Type Source #

Methods

from :: DecoratedTxOut -> Rep DecoratedTxOut x Source #

to :: Rep DecoratedTxOut x -> DecoratedTxOut Source #

Generic Script 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Script :: Type -> Type Source #

Methods

from :: Script -> Rep Script x Source #

to :: Rep Script x -> Script Source #

Generic DatumHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep DatumHash :: Type -> Type Source #

Methods

from :: DatumHash -> Rep DatumHash x Source #

to :: Rep DatumHash x -> DatumHash Source #

Generic StakingCredential 
Instance details

Defined in Plutus.V1.Ledger.Credential

Associated Types

type Rep StakingCredential :: Type -> Type Source #

Methods

from :: StakingCredential -> Rep StakingCredential x Source #

to :: Rep StakingCredential x -> StakingCredential Source #

Generic MintingPolicy 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep MintingPolicy :: Type -> Type Source #

Methods

from :: MintingPolicy -> Rep MintingPolicy x Source #

to :: Rep MintingPolicy x -> MintingPolicy Source #

Generic MintingPolicyHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep MintingPolicyHash :: Type -> Type Source #

Methods

from :: MintingPolicyHash -> Rep MintingPolicyHash x Source #

to :: Rep MintingPolicyHash x -> MintingPolicyHash Source #

Generic PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep PageSize :: Type -> Type Source #

Methods

from :: PageSize -> Rep PageSize x Source #

to :: Rep PageSize x -> PageSize Source #

Generic RedeemerHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep RedeemerHash :: Type -> Type Source #

Methods

from :: RedeemerHash -> Rep RedeemerHash x Source #

to :: Rep RedeemerHash x -> RedeemerHash Source #

Generic StakeValidator 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep StakeValidator :: Type -> Type Source #

Methods

from :: StakeValidator -> Rep StakeValidator x Source #

to :: Rep StakeValidator x -> StakeValidator Source #

Generic StakeValidatorHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep StakeValidatorHash :: Type -> Type Source #

Methods

from :: StakeValidatorHash -> Rep StakeValidatorHash x Source #

to :: Rep StakeValidatorHash x -> StakeValidatorHash Source #

Generic OpenApi 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OpenApi :: Type -> Type Source #

Methods

from :: OpenApi -> Rep OpenApi x Source #

to :: Rep OpenApi x -> OpenApi Source #

Generic NoContent 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep NoContent :: Type -> Type Source #

Methods

from :: NoContent -> Rep NoContent x Source #

to :: Rep NoContent x -> NoContent Source #

Generic TxId 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxId :: Type -> Type Source #

Methods

from :: TxId -> Rep TxId x Source #

to :: Rep TxId x -> TxId Source #

Generic ChainIndexTx 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTx :: Type -> Type Source #

Methods

from :: ChainIndexTx -> Rep ChainIndexTx x Source #

to :: Rep ChainIndexTx x -> ChainIndexTx Source #

Generic Diagnostics 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Diagnostics :: Type -> Type Source #

Methods

from :: Diagnostics -> Rep Diagnostics x Source #

to :: Rep Diagnostics x -> Diagnostics Source #

Generic Redeemer 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep Redeemer :: Type -> Type Source #

Methods

from :: Redeemer -> Rep Redeemer x Source #

to :: Rep Redeemer x -> Redeemer Source #

Generic Header 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Header :: Type -> Type Source #

Methods

from :: Header -> Rep Header x Source #

to :: Rep Header x -> Header Source #

Generic IsSecure 
Instance details

Defined in Servant.API.IsSecure

Associated Types

type Rep IsSecure :: Type -> Type Source #

Methods

from :: IsSecure -> Rep IsSecure x Source #

to :: Rep IsSecure x -> IsSecure Source #

Generic OpenApiType 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OpenApiType :: Type -> Type Source #

Methods

from :: OpenApiType -> Rep OpenApiType x Source #

to :: Rep OpenApiType x -> OpenApiType Source #

Generic Server 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Server :: Type -> Type Source #

Methods

from :: Server -> Rep Server x Source #

to :: Rep Server x -> Server Source #

Generic PathItem 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep PathItem :: Type -> Type Source #

Methods

from :: PathItem -> Rep PathItem x Source #

to :: Rep PathItem x -> PathItem Source #

Generic Tag 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Tag :: Type -> Type Source #

Methods

from :: Tag -> Rep Tag x Source #

to :: Rep Tag x -> Tag Source #

Generic ExternalDocs 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ExternalDocs :: Type -> Type Source #

Methods

from :: ExternalDocs -> Rep ExternalDocs x Source #

to :: Rep ExternalDocs x -> ExternalDocs Source #

Generic Operation 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Operation :: Type -> Type Source #

Methods

from :: Operation -> Rep Operation x Source #

to :: Rep Operation x -> Operation Source #

Generic Info 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Info :: Type -> Type Source #

Methods

from :: Info -> Rep Info x Source #

to :: Rep Info x -> Info Source #

Generic Components 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Components :: Type -> Type Source #

Methods

from :: Components -> Rep Components x Source #

to :: Rep Components x -> Components Source #

Generic OpenApiSpecVersion 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OpenApiSpecVersion :: Type -> Type Source #

Methods

from :: OpenApiSpecVersion -> Rep OpenApiSpecVersion x Source #

to :: Rep OpenApiSpecVersion x -> OpenApiSpecVersion Source #

Generic MediaTypeObject 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep MediaTypeObject :: Type -> Type Source #

Methods

from :: MediaTypeObject -> Rep MediaTypeObject x Source #

to :: Rep MediaTypeObject x -> MediaTypeObject Source #

Generic Example 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Example :: Type -> Type Source #

Methods

from :: Example -> Rep Example x Source #

to :: Rep Example x -> Example Source #

Generic Encoding 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Encoding :: Type -> Type Source #

Methods

from :: Encoding -> Rep Encoding x Source #

to :: Rep Encoding x -> Encoding Source #

Generic RequestBody 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep RequestBody :: Type -> Type Source #

Methods

from :: RequestBody -> Rep RequestBody x Source #

to :: Rep RequestBody x -> RequestBody Source #

Generic Param 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Param :: Type -> Type Source #

Methods

from :: Param -> Rep Param x Source #

to :: Rep Param x -> Param Source #

Generic Style 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Generic Response 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Response :: Type -> Type Source #

Methods

from :: Response -> Rep Response x Source #

to :: Rep Response x -> Response Source #

Generic Link 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Link :: Type -> Type Source #

Methods

from :: Link -> Rep Link x Source #

to :: Rep Link x -> Link Source #

Generic Responses 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Responses :: Type -> Type Source #

Methods

from :: Responses -> Rep Responses x Source #

to :: Rep Responses x -> Responses Source #

Generic Callback 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Callback :: Type -> Type Source #

Methods

from :: Callback -> Rep Callback x Source #

to :: Rep Callback x -> Callback Source #

Generic AcceptHeader 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep AcceptHeader :: Type -> Type Source #

Methods

from :: AcceptHeader -> Rep AcceptHeader x Source #

to :: Rep AcceptHeader x -> AcceptHeader Source #

Generic BlockNumber 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep BlockNumber :: Type -> Type Source #

Methods

from :: BlockNumber -> Rep BlockNumber x Source #

to :: Rep BlockNumber x -> BlockNumber Source #

Generic ChainIndexTxOut 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTxOut :: Type -> Type Source #

Methods

from :: ChainIndexTxOut -> Rep ChainIndexTxOut x Source #

to :: Rep ChainIndexTxOut x -> ChainIndexTxOut Source #

Generic ChainIndexTxOutputs 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTxOutputs :: Type -> Type Source #

Methods

from :: ChainIndexTxOutputs -> Rep ChainIndexTxOutputs x Source #

to :: Rep ChainIndexTxOutputs x -> ChainIndexTxOutputs Source #

Generic Depth 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Depth :: Type -> Type Source #

Methods

from :: Depth -> Rep Depth x Source #

to :: Rep Depth x -> Depth Source #

Generic Point 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Point :: Type -> Type Source #

Methods

from :: Point -> Rep Point x Source #

to :: Rep Point x -> Point Source #

Generic ReferenceScript 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ReferenceScript :: Type -> Type Source #

Methods

from :: ReferenceScript -> Rep ReferenceScript x Source #

to :: Rep ReferenceScript x -> ReferenceScript Source #

Generic TxConfirmedState 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxConfirmedState :: Type -> Type Source #

Methods

from :: TxConfirmedState -> Rep TxConfirmedState x Source #

to :: Rep TxConfirmedState x -> TxConfirmedState Source #

Generic TxIdState 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxIdState :: Type -> Type Source #

Methods

from :: TxIdState -> Rep TxIdState x Source #

to :: Rep TxIdState x -> TxIdState Source #

Generic TxOutBalance 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxOutBalance :: Type -> Type Source #

Methods

from :: TxOutBalance -> Rep TxOutBalance x Source #

to :: Rep TxOutBalance x -> TxOutBalance Source #

Generic TxOutState 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxOutState :: Type -> Type Source #

Methods

from :: TxOutState -> Rep TxOutState x Source #

to :: Rep TxOutState x -> TxOutState Source #

Generic TxUtxoBalance 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxUtxoBalance :: Type -> Type Source #

Methods

from :: TxUtxoBalance -> Rep TxUtxoBalance x Source #

to :: Rep TxUtxoBalance x -> TxUtxoBalance Source #

Generic TxValidity 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxValidity :: Type -> Type Source #

Methods

from :: TxValidity -> Rep TxValidity x Source #

to :: Rep TxValidity x -> TxValidity Source #

Generic BlockId 
Instance details

Defined in Ledger.Blockchain

Associated Types

type Rep BlockId :: Type -> Type Source #

Methods

from :: BlockId -> Rep BlockId x Source #

to :: Rep BlockId x -> BlockId Source #

Generic OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Associated Types

type Rep OutputDatum :: Type -> Type Source #

Methods

from :: OutputDatum -> Rep OutputDatum x Source #

to :: Rep OutputDatum x -> OutputDatum Source #

Generic ScriptHash 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ScriptHash :: Type -> Type Source #

Methods

from :: ScriptHash -> Rep ScriptHash x Source #

to :: Rep ScriptHash x -> ScriptHash Source #

Generic RedeemerPtr 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep RedeemerPtr :: Type -> Type Source #

Methods

from :: RedeemerPtr -> Rep RedeemerPtr x Source #

to :: Rep RedeemerPtr x -> RedeemerPtr Source #

Generic ScriptTag 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep ScriptTag :: Type -> Type Source #

Methods

from :: ScriptTag -> Rep ScriptTag x Source #

to :: Rep ScriptTag x -> ScriptTag Source #

Generic Language 
Instance details

Defined in Cardano.Ledger.Alonzo.Language

Associated Types

type Rep Language :: Type -> Type Source #

Methods

from :: Language -> Rep Language x Source #

to :: Rep Language x -> Language Source #

Generic ApiKeyParams 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ApiKeyParams :: Type -> Type Source #

Methods

from :: ApiKeyParams -> Rep ApiKeyParams x Source #

to :: Rep ApiKeyParams x -> ApiKeyParams Source #

Generic SecuritySchemeType 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep SecuritySchemeType :: Type -> Type Source #

Methods

from :: SecuritySchemeType -> Rep SecuritySchemeType x Source #

to :: Rep SecuritySchemeType x -> SecuritySchemeType Source #

Generic HttpSchemeType 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep HttpSchemeType :: Type -> Type Source #

Methods

from :: HttpSchemeType -> Rep HttpSchemeType x Source #

to :: Rep HttpSchemeType x -> HttpSchemeType Source #

Generic OAuth2Flows 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OAuth2Flows :: Type -> Type Source #

Methods

from :: OAuth2Flows -> Rep OAuth2Flows x Source #

to :: Rep OAuth2Flows x -> OAuth2Flows Source #

Generic Xml 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Xml :: Type -> Type Source #

Methods

from :: Xml -> Rep Xml x Source #

to :: Rep Xml x -> Xml Source #

Generic OAuth2AuthorizationCodeFlow 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OAuth2AuthorizationCodeFlow :: Type -> Type Source #

Methods

from :: OAuth2AuthorizationCodeFlow -> Rep OAuth2AuthorizationCodeFlow x Source #

to :: Rep OAuth2AuthorizationCodeFlow x -> OAuth2AuthorizationCodeFlow Source #

Generic OAuth2ImplicitFlow 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OAuth2ImplicitFlow :: Type -> Type Source #

Methods

from :: OAuth2ImplicitFlow -> Rep OAuth2ImplicitFlow x Source #

to :: Rep OAuth2ImplicitFlow x -> OAuth2ImplicitFlow Source #

Generic OAuth2ClientCredentialsFlow 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OAuth2ClientCredentialsFlow :: Type -> Type Source #

Methods

from :: OAuth2ClientCredentialsFlow -> Rep OAuth2ClientCredentialsFlow x Source #

to :: Rep OAuth2ClientCredentialsFlow x -> OAuth2ClientCredentialsFlow Source #

Generic Contact 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Contact :: Type -> Type Source #

Methods

from :: Contact -> Rep Contact x Source #

to :: Rep Contact x -> Contact Source #

Generic ServerVariable 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ServerVariable :: Type -> Type Source #

Methods

from :: ServerVariable -> Rep ServerVariable x Source #

to :: Rep ServerVariable x -> ServerVariable Source #

Generic SecurityScheme 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep SecurityScheme :: Type -> Type Source #

Methods

from :: SecurityScheme -> Rep SecurityScheme x Source #

to :: Rep SecurityScheme x -> SecurityScheme Source #

Generic Discriminator 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep Discriminator :: Type -> Type Source #

Methods

from :: Discriminator -> Rep Discriminator x Source #

to :: Rep Discriminator x -> Discriminator Source #

Generic ParamLocation 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ParamLocation :: Type -> Type Source #

Methods

from :: ParamLocation -> Rep ParamLocation x Source #

to :: Rep ParamLocation x -> ParamLocation Source #

Generic License 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep License :: Type -> Type Source #

Methods

from :: License -> Rep License x Source #

to :: Rep License x -> License Source #

Generic ExpressionOrValue 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ExpressionOrValue :: Type -> Type Source #

Methods

from :: ExpressionOrValue -> Rep ExpressionOrValue x Source #

to :: Rep ExpressionOrValue x -> ExpressionOrValue Source #

Generic OAuth2PasswordFlow 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep OAuth2PasswordFlow :: Type -> Type Source #

Methods

from :: OAuth2PasswordFlow -> Rep OAuth2PasswordFlow x Source #

to :: Rep OAuth2PasswordFlow x -> OAuth2PasswordFlow Source #

Generic SecurityDefinitions 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep SecurityDefinitions :: Type -> Type Source #

Methods

from :: SecurityDefinitions -> Rep SecurityDefinitions x Source #

to :: Rep SecurityDefinitions x -> SecurityDefinitions Source #

Generic ApiKeyLocation 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep ApiKeyLocation :: Type -> Type Source #

Methods

from :: ApiKeyLocation -> Rep ApiKeyLocation x Source #

to :: Rep ApiKeyLocation x -> ApiKeyLocation Source #

Generic ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

type Rep ProtocolParameters :: Type -> Type Source #

Methods

from :: ProtocolParameters -> Rep ProtocolParameters x Source #

to :: Rep ProtocolParameters x -> ProtocolParameters Source #

Generic PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

type Rep PraosNonce :: Type -> Type Source #

Methods

from :: PraosNonce -> Rep PraosNonce x Source #

to :: Rep PraosNonce x -> PraosNonce Source #

Generic NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

Associated Types

type Rep NetworkMagic :: Type -> Type Source #

Methods

from :: NetworkMagic -> Rep NetworkMagic x Source #

to :: Rep NetworkMagic x -> NetworkMagic Source #

Generic SlotConfig 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.TimeSlot

Associated Types

type Rep SlotConfig :: Type -> Type Source #

Methods

from :: SlotConfig -> Rep SlotConfig x Source #

to :: Rep SlotConfig x -> SlotConfig Source #

Generic POSIXTime 
Instance details

Defined in Plutus.V1.Ledger.Time

Associated Types

type Rep POSIXTime :: Type -> Type Source #

Methods

from :: POSIXTime -> Rep POSIXTime x Source #

to :: Rep POSIXTime x -> POSIXTime Source #

Generic EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochSize :: Type -> Type Source #

Methods

from :: EpochSize -> Rep EpochSize x Source #

to :: Rep EpochSize x -> EpochSize Source #

Generic EraParams 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.EraParams

Associated Types

type Rep EraParams :: Type -> Type Source #

Methods

from :: EraParams -> Rep EraParams x Source #

to :: Rep EraParams x -> EraParams Source #

Generic EraSummary 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

Associated Types

type Rep EraSummary :: Type -> Type Source #

Methods

from :: EraSummary -> Rep EraSummary x Source #

to :: Rep EraSummary x -> EraSummary Source #

Generic Bound 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

Associated Types

type Rep Bound :: Type -> Type Source #

Methods

from :: Bound -> Rep Bound x Source #

to :: Rep Bound x -> Bound Source #

Generic Globals 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Globals :: Type -> Type Source #

Methods

from :: Globals -> Rep Globals x Source #

to :: Rep Globals x -> Globals Source #

Generic UnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep UnitInterval :: Type -> Type Source #

Methods

from :: UnitInterval -> Rep UnitInterval x Source #

to :: Rep UnitInterval x -> UnitInterval Source #

Generic Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Nonce :: Type -> Type Source #

Methods

from :: Nonce -> Rep Nonce x Source #

to :: Rep Nonce x -> Nonce Source #

Generic Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

type Rep Coin :: Type -> Type Source #

Methods

from :: Coin -> Rep Coin x Source #

to :: Rep Coin x -> Coin Source #

Generic SlotLength 
Instance details

Defined in Cardano.Slotting.Time

Associated Types

type Rep SlotLength :: Type -> Type Source #

Methods

from :: SlotLength -> Rep SlotLength x Source #

to :: Rep SlotLength x -> SlotLength Source #

Generic ConnectionError 
Instance details

Defined in Plutus.Script.Utils.V1.Typed.Scripts.Validators

Associated Types

type Rep ConnectionError :: Type -> Type Source #

Methods

from :: ConnectionError -> Rep ConnectionError x Source #

to :: Rep ConnectionError x -> ConnectionError Source #

Generic Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Associated Types

type Rep Address :: Type -> Type Source #

Methods

from :: Address -> Rep Address x Source #

to :: Rep Address x -> Address Source #

Generic WrongOutTypeError 
Instance details

Defined in Plutus.Script.Utils.V1.Typed.Scripts.Validators

Associated Types

type Rep WrongOutTypeError :: Type -> Type Source #

Methods

from :: WrongOutTypeError -> Rep WrongOutTypeError x Source #

to :: Rep WrongOutTypeError x -> WrongOutTypeError Source #

Generic Certificate 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep Certificate :: Type -> Type Source #

Methods

from :: Certificate -> Rep Certificate x Source #

to :: Rep Certificate x -> Certificate Source #

Generic TxOut 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep TxOut :: Type -> Type Source #

Methods

from :: TxOut -> Rep TxOut x Source #

to :: Rep TxOut x -> TxOut Source #

Generic Withdrawal 
Instance details

Defined in Ledger.Tx.Internal

Associated Types

type Rep Withdrawal :: Type -> Type Source #

Methods

from :: Withdrawal -> Rep Withdrawal x Source #

to :: Rep Withdrawal x -> Withdrawal Source #

Generic CardanoBuildTx 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Associated Types

type Rep CardanoBuildTx :: Type -> Type Source #

Methods

from :: CardanoBuildTx -> Rep CardanoBuildTx x Source #

to :: Rep CardanoBuildTx x -> CardanoBuildTx Source #

Generic RdmrPtr 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWitness

Associated Types

type Rep RdmrPtr :: Type -> Type Source #

Methods

from :: RdmrPtr -> Rep RdmrPtr x Source #

to :: Rep RdmrPtr x -> RdmrPtr Source #

Generic ExUnits 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep ExUnits :: Type -> Type Source #

Methods

from :: ExUnits -> Rep ExUnits x Source #

to :: Rep ExUnits x -> ExUnits Source #

Generic TxOut 
Instance details

Defined in Plutus.V2.Ledger.Tx

Associated Types

type Rep TxOut :: Type -> Type Source #

Methods

from :: TxOut -> Rep TxOut x Source #

to :: Rep TxOut x -> TxOut Source #

Generic ValidationResult 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationResult :: Type -> Type Source #

Methods

from :: ValidationResult -> Rep ValidationResult x Source #

to :: Rep ValidationResult x -> ValidationResult Source #

Generic ValidationResultSimple 
Instance details

Defined in Ledger.Index.Internal

Associated Types

type Rep ValidationResultSimple :: Type -> Type Source #

Methods

from :: ValidationResultSimple -> Rep ValidationResultSimple x Source #

to :: Rep ValidationResultSimple x -> ValidationResultSimple Source #

Generic Address 
Instance details

Defined in Cardano.Chain.Common.Address

Associated Types

type Rep Address :: Type -> Type Source #

Methods

from :: Address -> Rep Address x Source #

to :: Rep Address x -> Address Source #

Generic ScriptError 
Instance details

Defined in Plutus.V1.Ledger.Scripts

Associated Types

type Rep ScriptError :: Type -> Type Source #

Methods

from :: ScriptError -> Rep ScriptError x Source #

to :: Rep ScriptError x -> ScriptError Source #

Generic FromCardanoError 
Instance details

Defined in Ledger.Tx.CardanoAPI.Internal

Associated Types

type Rep FromCardanoError :: Type -> Type Source #

Methods

from :: FromCardanoError -> Rep FromCardanoError x Source #

to :: Rep FromCardanoError x -> FromCardanoError Source #

Generic SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep SlotNo :: Type -> Type Source #

Methods

from :: SlotNo -> Rep SlotNo x Source #

to :: Rep SlotNo x -> SlotNo Source #

Generic TxOut 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxOut :: Type -> Type Source #

Methods

from :: TxOut -> Rep TxOut x Source #

to :: Rep TxOut x -> TxOut Source #

Generic Counter 
Instance details

Defined in Cardano.BM.Data.Counter

Associated Types

type Rep Counter :: Type -> Type Source #

Methods

from :: Counter -> Rep Counter x Source #

to :: Rep Counter x -> Counter Source #

Generic CounterState 
Instance details

Defined in Cardano.BM.Data.Counter

Associated Types

type Rep CounterState :: Type -> Type Source #

Methods

from :: CounterState -> Rep CounterState x Source #

to :: Rep CounterState x -> CounterState Source #

Generic CounterType 
Instance details

Defined in Cardano.BM.Data.Counter

Associated Types

type Rep CounterType :: Type -> Type Source #

Methods

from :: CounterType -> Rep CounterType x Source #

to :: Rep CounterType x -> CounterType Source #

Generic Measurable 
Instance details

Defined in Cardano.BM.Data.Aggregated

Associated Types

type Rep Measurable :: Type -> Type Source #

Methods

from :: Measurable -> Rep Measurable x Source #

to :: Rep Measurable x -> Measurable Source #

Generic ScriptPurpose 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep ScriptPurpose :: Type -> Type Source #

Methods

from :: ScriptPurpose -> Rep ScriptPurpose x Source #

to :: Rep ScriptPurpose x -> ScriptPurpose Source #

Generic DCert 
Instance details

Defined in Plutus.V1.Ledger.DCert

Associated Types

type Rep DCert :: Type -> Type Source #

Methods

from :: DCert -> Rep DCert x Source #

to :: Rep DCert x -> DCert Source #

Generic PaymentPubKey 
Instance details

Defined in Ledger.Address

Associated Types

type Rep PaymentPubKey :: Type -> Type Source #

Methods

from :: PaymentPubKey -> Rep PaymentPubKey x Source #

to :: Rep PaymentPubKey x -> PaymentPubKey Source #

Generic StakePubKey 
Instance details

Defined in Ledger.Address

Associated Types

type Rep StakePubKey :: Type -> Type Source #

Methods

from :: StakePubKey -> Rep StakePubKey x Source #

to :: Rep StakePubKey x -> StakePubKey Source #

Generic StakePubKeyHash 
Instance details

Defined in Ledger.Address

Associated Types

type Rep StakePubKeyHash :: Type -> Type Source #

Methods

from :: StakePubKeyHash -> Rep StakePubKeyHash x Source #

to :: Rep StakePubKeyHash x -> StakePubKeyHash Source #

Generic PubKey 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep PubKey :: Type -> Type Source #

Methods

from :: PubKey -> Rep PubKey x Source #

to :: Rep PubKey x -> PubKey Source #

Generic LedgerBytes 
Instance details

Defined in Plutus.V1.Ledger.Bytes

Associated Types

type Rep LedgerBytes :: Type -> Type Source #

Methods

from :: LedgerBytes -> Rep LedgerBytes x Source #

to :: Rep LedgerBytes x -> LedgerBytes Source #

Generic PrivateKey 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep PrivateKey :: Type -> Type Source #

Methods

from :: PrivateKey -> Rep PrivateKey x Source #

to :: Rep PrivateKey x -> PrivateKey Source #

Generic ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep ProtVer :: Type -> Type Source #

Methods

from :: ProtVer -> Rep ProtVer x Source #

to :: Rep ProtVer x -> ProtVer Source #

Generic ByronPartialLedgerConfig 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

Associated Types

type Rep ByronPartialLedgerConfig :: Type -> Type Source #

Methods

from :: ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x Source #

to :: Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig Source #

Generic BinaryBlockInfo 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

Associated Types

type Rep BinaryBlockInfo :: Type -> Type Source #

Methods

from :: BinaryBlockInfo -> Rep BinaryBlockInfo x Source #

to :: Rep BinaryBlockInfo x -> BinaryBlockInfo Source #

Generic TriggerHardFork 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

Associated Types

type Rep TriggerHardFork :: Type -> Type Source #

Methods

from :: TriggerHardFork -> Rep TriggerHardFork x Source #

to :: Rep TriggerHardFork x -> TriggerHardFork Source #

Generic MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Associated Types

type Rep MaxMajorProtVer :: Type -> Type Source #

Methods

from :: MaxMajorProtVer -> Rep MaxMajorProtVer x Source #

to :: Rep MaxMajorProtVer x -> MaxMajorProtVer Source #

Generic PrefixLen 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

Associated Types

type Rep PrefixLen :: Type -> Type Source #

Methods

from :: PrefixLen -> Rep PrefixLen x Source #

to :: Rep PrefixLen x -> PrefixLen Source #

Generic EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Associated Types

type Rep EpochSlots :: Type -> Type Source #

Methods

from :: EpochSlots -> Rep EpochSlots x Source #

to :: Rep EpochSlots x -> EpochSlots Source #

Generic Config 
Instance details

Defined in Cardano.Chain.Genesis.Config

Associated Types

type Rep Config :: Type -> Type Source #

Methods

from :: Config -> Rep Config x Source #

to :: Rep Config x -> Config Source #

Generic CompactAddress 
Instance details

Defined in Cardano.Chain.Common.Compact

Associated Types

type Rep CompactAddress :: Type -> Type Source #

Methods

from :: CompactAddress -> Rep CompactAddress x Source #

to :: Rep CompactAddress x -> CompactAddress Source #

Generic RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Associated Types

type Rep RequiresNetworkMagic :: Type -> Type Source #

Methods

from :: RequiresNetworkMagic -> Rep RequiresNetworkMagic x Source #

to :: Rep RequiresNetworkMagic x -> RequiresNetworkMagic Source #

Generic ProtocolParameters 
Instance details

Defined in Cardano.Chain.Update.ProtocolParameters

Associated Types

type Rep ProtocolParameters :: Type -> Type Source #

Methods

from :: ProtocolParameters -> Rep ProtocolParameters x Source #

to :: Rep ProtocolParameters x -> ProtocolParameters Source #

Generic EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochNo :: Type -> Type Source #

Methods

from :: EpochNo -> Rep EpochNo x Source #

to :: Rep EpochNo x -> EpochNo Source #

Generic BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Associated Types

type Rep BlockNo :: Type -> Type Source #

Methods

from :: BlockNo -> Rep BlockNo x Source #

to :: Rep BlockNo x -> BlockNo Source #

Generic ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

Associated Types

type Rep ProtocolVersion :: Type -> Type Source #

Methods

from :: ProtocolVersion -> Rep ProtocolVersion x Source #

to :: Rep ProtocolVersion x -> ProtocolVersion Source #

Generic PBftSignatureThreshold 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSignatureThreshold :: Type -> Type Source #

Methods

from :: PBftSignatureThreshold -> Rep PBftSignatureThreshold x Source #

to :: Rep PBftSignatureThreshold x -> PBftSignatureThreshold Source #

Generic ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Associated Types

type Rep ProtocolMagicId :: Type -> Type Source #

Methods

from :: ProtocolMagicId -> Rep ProtocolMagicId x Source #

to :: Rep ProtocolMagicId x -> ProtocolMagicId Source #

Generic ChunkInfo 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal

Associated Types

type Rep ChunkInfo :: Type -> Type Source #

Methods

from :: ChunkInfo -> Rep ChunkInfo x Source #

to :: Rep ChunkInfo x -> ChunkInfo Source #

Generic CoreNodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

Associated Types

type Rep CoreNodeId :: Type -> Type Source #

Methods

from :: CoreNodeId -> Rep CoreNodeId x Source #

to :: Rep CoreNodeId x -> CoreNodeId Source #

Generic SoftwareVersion 
Instance details

Defined in Cardano.Chain.Update.SoftwareVersion

Associated Types

type Rep SoftwareVersion :: Type -> Type Source #

Methods

from :: SoftwareVersion -> Rep SoftwareVersion x Source #

to :: Rep SoftwareVersion x -> SoftwareVersion Source #

Generic CompactRedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Compact

Associated Types

type Rep CompactRedeemVerificationKey :: Type -> Type Source #

Methods

from :: CompactRedeemVerificationKey -> Rep CompactRedeemVerificationKey x Source #

to :: Rep CompactRedeemVerificationKey x -> CompactRedeemVerificationKey Source #

Generic Lovelace 
Instance details

Defined in Cardano.Chain.Common.Lovelace

Associated Types

type Rep Lovelace :: Type -> Type Source #

Methods

from :: Lovelace -> Rep Lovelace x Source #

to :: Rep Lovelace x -> Lovelace Source #

Generic ChainValidationState 
Instance details

Defined in Cardano.Chain.Block.Validation

Associated Types

type Rep ChainValidationState :: Type -> Type Source #

Methods

from :: ChainValidationState -> Rep ChainValidationState x Source #

to :: Rep ChainValidationState x -> ChainValidationState Source #

Generic VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Associated Types

type Rep VerificationKey :: Type -> Type Source #

Methods

from :: VerificationKey -> Rep VerificationKey x Source #

to :: Rep VerificationKey x -> VerificationKey Source #

Generic GenesisHash 
Instance details

Defined in Cardano.Chain.Genesis.Hash

Associated Types

type Rep GenesisHash :: Type -> Type Source #

Methods

from :: GenesisHash -> Rep GenesisHash x Source #

to :: Rep GenesisHash x -> GenesisHash Source #

Generic CandidateProtocolUpdate 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

Associated Types

type Rep CandidateProtocolUpdate :: Type -> Type Source #

Methods

from :: CandidateProtocolUpdate -> Rep CandidateProtocolUpdate x Source #

to :: Rep CandidateProtocolUpdate x -> CandidateProtocolUpdate Source #

Generic SlotNumber 
Instance details

Defined in Cardano.Chain.Slotting.SlotNumber

Associated Types

type Rep SlotNumber :: Type -> Type Source #

Methods

from :: SlotNumber -> Rep SlotNumber x Source #

to :: Rep SlotNumber x -> SlotNumber Source #

Generic Endorsement 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

Associated Types

type Rep Endorsement :: Type -> Type Source #

Methods

from :: Endorsement -> Rep Endorsement x Source #

to :: Rep Endorsement x -> Endorsement Source #

Generic ByronHash 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Associated Types

type Rep ByronHash :: Type -> Type Source #

Methods

from :: ByronHash -> Rep ByronHash x Source #

to :: Rep ByronHash x -> ByronHash Source #

Generic Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Associated Types

type Rep Tx :: Type -> Type Source #

Methods

from :: Tx -> Rep Tx x Source #

to :: Rep Tx x -> Tx Source #

Generic ByteSpan 
Instance details

Defined in Cardano.Binary.Annotated

Associated Types

type Rep ByteSpan :: Type -> Type Source #

Methods

from :: ByteSpan -> Rep ByteSpan x Source #

to :: Rep ByteSpan x -> ByteSpan Source #

Generic ByronTransition 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep ByronTransition :: Type -> Type Source #

Methods

from :: ByronTransition -> Rep ByronTransition x Source #

to :: Rep ByronTransition x -> ByronTransition Source #

Generic Map 
Instance details

Defined in Cardano.Chain.Delegation.Map

Associated Types

type Rep Map :: Type -> Type Source #

Methods

from :: Map -> Rep Map x Source #

to :: Rep Map x -> Map Source #

Generic ScheduledDelegation 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

Associated Types

type Rep ScheduledDelegation :: Type -> Type Source #

Methods

from :: ScheduledDelegation -> Rep ScheduledDelegation x Source #

to :: Rep ScheduledDelegation x -> ScheduledDelegation Source #

Generic EpochNumber 
Instance details

Defined in Cardano.Chain.Slotting.EpochNumber

Associated Types

type Rep EpochNumber :: Type -> Type Source #

Methods

from :: EpochNumber -> Rep EpochNumber x Source #

to :: Rep EpochNumber x -> EpochNumber Source #

Generic State 
Instance details

Defined in Cardano.Chain.Update.Validation.Interface

Associated Types

type Rep State :: Type -> Type Source #

Methods

from :: State -> Rep State x Source #

to :: Rep State x -> State Source #

Generic UTxO 
Instance details

Defined in Cardano.Chain.UTxO.UTxO

Associated Types

type Rep UTxO :: Type -> Type Source #

Methods

from :: UTxO -> Rep UTxO x Source #

to :: Rep UTxO x -> UTxO Source #

Generic ByronOtherHeaderEnvelopeError 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.HeaderValidation

Associated Types

type Rep ByronOtherHeaderEnvelopeError :: Type -> Type Source #

Methods

from :: ByronOtherHeaderEnvelopeError -> Rep ByronOtherHeaderEnvelopeError x Source #

to :: Rep ByronOtherHeaderEnvelopeError x -> ByronOtherHeaderEnvelopeError Source #

Generic PBftSelectView 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSelectView :: Type -> Type Source #

Methods

from :: PBftSelectView -> Rep PBftSelectView x Source #

to :: Rep PBftSelectView x -> PBftSelectView Source #

Generic ToSign 
Instance details

Defined in Cardano.Chain.Block.Header

Associated Types

type Rep ToSign :: Type -> Type Source #

Methods

from :: ToSign -> Rep ToSign x Source #

to :: Rep ToSign x -> ToSign Source #

Generic PraosEnvelopeError 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

Associated Types

type Rep PraosEnvelopeError :: Type -> Type Source #

Methods

from :: PraosEnvelopeError -> Rep PraosEnvelopeError x Source #

to :: Rep PraosEnvelopeError x -> PraosEnvelopeError Source #

Generic PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep PositiveUnitInterval :: Type -> Type Source #

Methods

from :: PositiveUnitInterval -> Rep PositiveUnitInterval x Source #

to :: Rep PositiveUnitInterval x -> PositiveUnitInterval Source #

Generic Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Network :: Type -> Type Source #

Methods

from :: Network -> Rep Network x Source #

to :: Rep Network x -> Network Source #

Generic PraosParams 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep PraosParams :: Type -> Type Source #

Methods

from :: PraosParams -> Rep PraosParams x Source #

to :: Rep PraosParams x -> PraosParams Source #

Generic TPraosParams 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep TPraosParams :: Type -> Type Source #

Methods

from :: TPraosParams -> Rep TPraosParams x Source #

to :: Rep TPraosParams x -> TPraosParams Source #

Generic KESInfo 
Instance details

Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey

Associated Types

type Rep KESInfo :: Type -> Type Source #

Methods

from :: KESInfo -> Rep KESInfo x Source #

to :: Rep KESInfo x -> KESInfo Source #

Generic AlonzoMeasure 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep AlonzoMeasure :: Type -> Type Source #

Methods

from :: AlonzoMeasure -> Rep AlonzoMeasure x Source #

to :: Rep AlonzoMeasure x -> AlonzoMeasure Source #

Generic StakePoolRelay 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep StakePoolRelay :: Type -> Type Source #

Methods

from :: StakePoolRelay -> Rep StakePoolRelay x Source #

to :: Rep StakePoolRelay x -> StakePoolRelay Source #

Generic RewardParams 
Instance details

Defined in Cardano.Ledger.Shelley.API.Wallet

Associated Types

type Rep RewardParams :: Type -> Type Source #

Methods

from :: RewardParams -> Rep RewardParams x Source #

to :: Rep RewardParams x -> RewardParams Source #

Generic RewardInfoPool 
Instance details

Defined in Cardano.Ledger.Shelley.API.Wallet

Associated Types

type Rep RewardInfoPool :: Type -> Type Source #

Methods

from :: RewardInfoPool -> Rep RewardInfoPool x Source #

to :: Rep RewardInfoPool x -> RewardInfoPool Source #

Generic NonNegativeInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep NonNegativeInterval :: Type -> Type Source #

Methods

from :: NonNegativeInterval -> Rep NonNegativeInterval x Source #

to :: Rep NonNegativeInterval x -> NonNegativeInterval Source #

Generic ShelleyTransition 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep ShelleyTransition :: Type -> Type Source #

Methods

from :: ShelleyTransition -> Rep ShelleyTransition x Source #

to :: Rep ShelleyTransition x -> ShelleyTransition Source #

Generic SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Associated Types

type Rep SystemStart :: Type -> Type Source #

Methods

from :: SystemStart -> Rep SystemStart x Source #

to :: Rep SystemStart x -> SystemStart Source #

Generic SecurityParam 
Instance details

Defined in Ouroboros.Consensus.Config.SecurityParam

Associated Types

type Rep SecurityParam :: Type -> Type Source #

Methods

from :: SecurityParam -> Rep SecurityParam x Source #

to :: Rep SecurityParam x -> SecurityParam Source #

Generic Past 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep Past :: Type -> Type Source #

Methods

from :: Past -> Rep Past x Source #

to :: Rep Past x -> Past Source #

Generic TransitionInfo 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep TransitionInfo :: Type -> Type Source #

Methods

from :: TransitionInfo -> Rep TransitionInfo x Source #

to :: Rep TransitionInfo x -> TransitionInfo Source #

Generic RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

Associated Types

type Rep RelativeTime :: Type -> Type Source #

Methods

from :: RelativeTime -> Rep RelativeTime x Source #

to :: Rep RelativeTime x -> RelativeTime Source #

Generic FsPath 
Instance details

Defined in Ouroboros.Consensus.Storage.FS.API.Types

Associated Types

type Rep FsPath :: Type -> Type Source #

Methods

from :: FsPath -> Rep FsPath x Source #

to :: Rep FsPath x -> FsPath Source #

Generic Time 
Instance details

Defined in Control.Monad.Class.MonadTime

Associated Types

type Rep Time :: Type -> Type Source #

Methods

from :: Time -> Rep Time x Source #

to :: Rep Time x -> Time Source #

Generic ChainPredicateFailure 
Instance details

Defined in Cardano.Ledger.Chain

Associated Types

type Rep ChainPredicateFailure :: Type -> Type Source #

Methods

from :: ChainPredicateFailure -> Rep ChainPredicateFailure x Source #

to :: Rep ChainPredicateFailure x -> ChainPredicateFailure Source #

Generic AccountState 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep AccountState :: Type -> Type Source #

Methods

from :: AccountState -> Rep AccountState x Source #

to :: Rep AccountState x -> AccountState Source #

Generic Ptr 
Instance details

Defined in Cardano.Ledger.Credential

Associated Types

type Rep Ptr :: Type -> Type Source #

Methods

from :: Ptr -> Rep Ptr x Source #

to :: Rep Ptr x -> Ptr Source #

Generic DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

type Rep DeltaCoin :: Type -> Type Source #

Methods

from :: DeltaCoin -> Rep DeltaCoin x Source #

to :: Rep DeltaCoin x -> DeltaCoin Source #

Generic LogWeight 
Instance details

Defined in Cardano.Ledger.Shelley.PoolRank

Associated Types

type Rep LogWeight :: Type -> Type Source #

Methods

from :: LogWeight -> Rep LogWeight x Source #

to :: Rep LogWeight x -> LogWeight Source #

Generic Likelihood 
Instance details

Defined in Cardano.Ledger.Shelley.PoolRank

Associated Types

type Rep Likelihood :: Type -> Type Source #

Methods

from :: Likelihood -> Rep Likelihood x Source #

to :: Rep Likelihood x -> Likelihood Source #

Generic RewardType 
Instance details

Defined in Cardano.Ledger.Shelley.Rewards

Associated Types

type Rep RewardType :: Type -> Type Source #

Methods

from :: RewardType -> Rep RewardType x Source #

to :: Rep RewardType x -> RewardType Source #

Generic CostModels 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep CostModels :: Type -> Type Source #

Methods

from :: CostModels -> Rep CostModels x Source #

to :: Rep CostModels x -> CostModels Source #

Generic Prices 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep Prices :: Type -> Type Source #

Methods

from :: Prices -> Rep Prices x Source #

to :: Rep Prices x -> Prices Source #

Generic AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

Associated Types

type Rep AlonzoGenesis :: Type -> Type Source #

Methods

from :: AlonzoGenesis -> Rep AlonzoGenesis x Source #

to :: Rep AlonzoGenesis x -> AlonzoGenesis Source #

Generic Metadatum 
Instance details

Defined in Cardano.Ledger.Shelley.Metadata

Associated Types

type Rep Metadatum :: Type -> Type Source #

Methods

from :: Metadatum -> Rep Metadatum x Source #

to :: Rep Metadatum x -> Metadatum Source #

Generic CostModel 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep CostModel :: Type -> Type Source #

Methods

from :: CostModel -> Rep CostModel x Source #

to :: Rep CostModel x -> CostModel Source #

Generic ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExCPU :: Type -> Type Source #

Methods

from :: ExCPU -> Rep ExCPU x Source #

to :: Rep ExCPU x -> ExCPU Source #

Generic ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExMemory :: Type -> Type Source #

Methods

from :: ExMemory -> Rep ExMemory x Source #

to :: Rep ExMemory x -> ExMemory Source #

Generic ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Associated Types

type Rep ExBudget :: Type -> Type Source #

Methods

from :: ExBudget -> Rep ExBudget x Source #

to :: Rep ExBudget x -> ExBudget Source #

Generic Strictness 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep Strictness :: Type -> Type Source #

Methods

from :: Strictness -> Rep Strictness x Source #

to :: Rep Strictness x -> Strictness Source #

Generic Recursivity 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep Recursivity :: Type -> Type Source #

Methods

from :: Recursivity -> Rep Recursivity x Source #

to :: Rep Recursivity x -> Recursivity Source #

Generic NamedDeBruijn 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep NamedDeBruijn :: Type -> Type Source #

Methods

from :: NamedDeBruijn -> Rep NamedDeBruijn x Source #

to :: Rep NamedDeBruijn x -> NamedDeBruijn Source #

Generic NamedTyDeBruijn 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep NamedTyDeBruijn :: Type -> Type Source #

Methods

from :: NamedTyDeBruijn -> Rep NamedTyDeBruijn x Source #

to :: Rep NamedTyDeBruijn x -> NamedTyDeBruijn Source #

Generic Index 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep Index :: Type -> Type Source #

Methods

from :: Index -> Rep Index x Source #

to :: Rep Index x -> Index Source #

Generic TyDeBruijn 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep TyDeBruijn :: Type -> Type Source #

Methods

from :: TyDeBruijn -> Rep TyDeBruijn x Source #

to :: Rep TyDeBruijn x -> TyDeBruijn Source #

Generic ParseError 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep ParseError :: Type -> Type Source #

Methods

from :: ParseError -> Rep ParseError x Source #

to :: Rep ParseError x -> ParseError Source #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type Source #

Methods

from :: SourcePos -> Rep SourcePos x Source #

to :: Rep SourcePos x -> SourcePos Source #

Generic FreeVariableError 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep FreeVariableError :: Type -> Type Source #

Methods

from :: FreeVariableError -> Rep FreeVariableError x Source #

to :: Rep FreeVariableError x -> FreeVariableError Source #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type Source #

Methods

from :: ConstructorInfo -> Rep ConstructorInfo x Source #

to :: Rep ConstructorInfo x -> ConstructorInfo Source #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type Source #

Methods

from :: DatatypeInfo -> Rep DatatypeInfo x Source #

to :: Rep DatatypeInfo x -> DatatypeInfo Source #

Generic Desirability 
Instance details

Defined in Cardano.Ledger.Shelley.RewardProvenance

Associated Types

type Rep Desirability :: Type -> Type Source #

Methods

from :: Desirability -> Rep Desirability x Source #

to :: Rep Desirability x -> Desirability Source #

Generic PoolMetadata 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep PoolMetadata :: Type -> Type Source #

Methods

from :: PoolMetadata -> Rep PoolMetadata x Source #

to :: Rep PoolMetadata x -> PoolMetadata Source #

Generic IPv6 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv6 :: Type -> Type Source #

Methods

from :: IPv6 -> Rep IPv6 x Source #

to :: Rep IPv6 x -> IPv6 Source #

Generic IPv4 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv4 :: Type -> Type Source #

Methods

from :: IPv4 -> Rep IPv4 x Source #

to :: Rep IPv4 x -> IPv4 Source #

Generic AssetClassMap 
Instance details

Defined in Plutus.ChainIndex.Emulator.DiskState

Associated Types

type Rep AssetClassMap :: Type -> Type Source #

Methods

from :: AssetClassMap -> Rep AssetClassMap x Source #

to :: Rep AssetClassMap x -> AssetClassMap Source #

Generic CredentialMap 
Instance details

Defined in Plutus.ChainIndex.Emulator.DiskState

Associated Types

type Rep CredentialMap :: Type -> Type Source #

Methods

from :: CredentialMap -> Rep CredentialMap x Source #

to :: Rep CredentialMap x -> CredentialMap Source #

Generic DiskState 
Instance details

Defined in Plutus.ChainIndex.Emulator.DiskState

Associated Types

type Rep DiskState :: Type -> Type Source #

Methods

from :: DiskState -> Rep DiskState x Source #

to :: Rep DiskState x -> DiskState Source #

Generic ChainIndexEmulatorState 
Instance details

Defined in Plutus.ChainIndex.Emulator.Handlers

Associated Types

type Rep ChainIndexEmulatorState :: Type -> Type Source #

Methods

from :: ChainIndexEmulatorState -> Rep ChainIndexEmulatorState x Source #

to :: Rep ChainIndexEmulatorState x -> ChainIndexEmulatorState Source #

Generic ChainIndexError 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep ChainIndexError :: Type -> Type Source #

Methods

from :: ChainIndexError -> Rep ChainIndexError x Source #

to :: Rep ChainIndexError x -> ChainIndexError Source #

Generic ChainIndexLog 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Associated Types

type Rep ChainIndexLog :: Type -> Type Source #

Methods

from :: ChainIndexLog -> Rep ChainIndexLog x Source #

to :: Rep ChainIndexLog x -> ChainIndexLog Source #

Generic AssertionError 
Instance details

Defined in Plutus.Contract.Error

Associated Types

type Rep AssertionError :: Type -> Type Source #

Methods

from :: AssertionError -> Rep AssertionError x Source #

to :: Rep AssertionError x -> AssertionError Source #

Generic ChainIndexQuery 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep ChainIndexQuery :: Type -> Type Source #

Methods

from :: ChainIndexQuery -> Rep ChainIndexQuery x Source #

to :: Rep ChainIndexQuery x -> ChainIndexQuery Source #

Generic ChainIndexResponse 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep ChainIndexResponse :: Type -> Type Source #

Methods

from :: ChainIndexResponse -> Rep ChainIndexResponse x Source #

to :: Rep ChainIndexResponse x -> ChainIndexResponse Source #

Generic SlotConversionError 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.TimeSlot

Associated Types

type Rep SlotConversionError :: Type -> Type Source #

Methods

from :: SlotConversionError -> Rep SlotConversionError x Source #

to :: Rep SlotConversionError x -> SlotConversionError Source #

Generic Priority 
Instance details

Defined in Plutus.Trace.Scheduler

Associated Types

type Rep Priority :: Type -> Type Source #

Methods

from :: Priority -> Rep Priority x Source #

to :: Rep Priority x -> Priority Source #

Generic ThreadEvent 
Instance details

Defined in Plutus.Trace.Scheduler

Associated Types

type Rep ThreadEvent :: Type -> Type Source #

Methods

from :: ThreadEvent -> Rep ThreadEvent x Source #

to :: Rep ThreadEvent x -> ThreadEvent Source #

Generic Tag 
Instance details

Defined in Plutus.Trace.Tag

Associated Types

type Rep Tag :: Type -> Type Source #

Methods

from :: Tag -> Rep Tag x Source #

to :: Rep Tag x -> Tag Source #

Generic WalletEvent 
Instance details

Defined in Wallet.Emulator.Wallet

Associated Types

type Rep WalletEvent :: Type -> Type Source #

Methods

from :: WalletEvent -> Rep WalletEvent x Source #

to :: Rep WalletEvent x -> WalletEvent Source #

Generic NodeClientEvent 
Instance details

Defined in Wallet.Emulator.NodeClient

Associated Types

type Rep NodeClientEvent :: Type -> Type Source #

Methods

from :: NodeClientEvent -> Rep NodeClientEvent x Source #

to :: Rep NodeClientEvent x -> NodeClientEvent Source #

Generic InsertUtxoPosition 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Associated Types

type Rep InsertUtxoPosition :: Type -> Type Source #

Methods

from :: InsertUtxoPosition -> Rep InsertUtxoPosition x Source #

to :: Rep InsertUtxoPosition x -> InsertUtxoPosition Source #

Generic BeamLog 
Instance details

Defined in Control.Monad.Freer.Extras.Beam.Common

Associated Types

type Rep BeamLog :: Type -> Type Source #

Methods

from :: BeamLog -> Rep BeamLog x Source #

to :: Rep BeamLog x -> BeamLog Source #

Generic CheckpointLogMsg 
Instance details

Defined in Plutus.Contract.Checkpoint

Associated Types

type Rep CheckpointLogMsg :: Type -> Type Source #

Methods

from :: CheckpointLogMsg -> Rep CheckpointLogMsg x Source #

to :: Rep CheckpointLogMsg x -> CheckpointLogMsg Source #

Generic ChainState 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.Chain

Associated Types

type Rep ChainState :: Type -> Type Source #

Methods

from :: ChainState -> Rep ChainState x Source #

to :: Rep ChainState x -> ChainState Source #

Generic AddressMap 
Instance details

Defined in Ledger.AddressMap

Associated Types

type Rep AddressMap :: Type -> Type Source #

Methods

from :: AddressMap -> Rep AddressMap x Source #

to :: Rep AddressMap x -> AddressMap Source #

Generic WalletNumber 
Instance details

Defined in Ledger.CardanoWallet

Associated Types

type Rep WalletNumber :: Type -> Type Source #

Methods

from :: WalletNumber -> Rep WalletNumber x Source #

to :: Rep WalletNumber x -> WalletNumber Source #

Generic AnnotatedTx 
Instance details

Defined in Wallet.Rollup.Types

Associated Types

type Rep AnnotatedTx :: Type -> Type Source #

Methods

from :: AnnotatedTx -> Rep AnnotatedTx x Source #

to :: Rep AnnotatedTx x -> AnnotatedTx Source #

Generic BeneficialOwner 
Instance details

Defined in Wallet.Rollup.Types

Associated Types

type Rep BeneficialOwner :: Type -> Type Source #

Methods

from :: BeneficialOwner -> Rep BeneficialOwner x Source #

to :: Rep BeneficialOwner x -> BeneficialOwner Source #

Generic DereferencedInput 
Instance details

Defined in Wallet.Rollup.Types

Associated Types

type Rep DereferencedInput :: Type -> Type Source #

Methods

from :: DereferencedInput -> Rep DereferencedInput x Source #

to :: Rep DereferencedInput x -> DereferencedInput Source #

Generic Rollup 
Instance details

Defined in Wallet.Rollup.Types

Associated Types

type Rep Rollup :: Type -> Type Source #

Methods

from :: Rollup -> Rep Rollup x Source #

to :: Rep Rollup x -> Rollup Source #

Generic SequenceId 
Instance details

Defined in Wallet.Rollup.Types

Associated Types

type Rep SequenceId :: Type -> Type Source #

Methods

from :: SequenceId -> Rep SequenceId x Source #

to :: Rep SequenceId x -> SequenceId Source #

Generic IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Associated Types

type Rep IsValid :: Type -> Type Source #

Methods

from :: IsValid -> Rep IsValid x Source #

to :: Rep IsValid x -> IsValid Source #

Generic Outcome 
Instance details

Defined in Test.Tasty.Core

Associated Types

type Rep Outcome :: Type -> Type Source #

Methods

from :: Outcome -> Rep Outcome x Source #

to :: Rep Outcome x -> Outcome Source #

Generic Expr 
Instance details

Defined in Test.Tasty.Patterns.Types

Associated Types

type Rep Expr :: Type -> Type Source #

Methods

from :: Expr -> Rep Expr x Source #

to :: Rep Expr x -> Expr Source #

Generic ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Associated Types

type Rep ConcException :: Type -> Type Source #

Methods

from :: ConcException -> Rep ConcException x Source #

to :: Rep ConcException x -> ConcException Source #

Generic DatabaseStateSource 
Instance details

Defined in Database.Beam.Migrate.Actions

Associated Types

type Rep DatabaseStateSource :: Type -> Type Source #

Methods

from :: DatabaseStateSource -> Rep DatabaseStateSource x Source #

to :: Rep DatabaseStateSource x -> DatabaseStateSource Source #

Generic TableExistsPredicate 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep TableExistsPredicate :: Type -> Type Source #

Methods

from :: TableExistsPredicate -> Rep TableExistsPredicate x Source #

to :: Rep TableExistsPredicate x -> TableExistsPredicate Source #

Generic TableHasPrimaryKey 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep TableHasPrimaryKey :: Type -> Type Source #

Methods

from :: TableHasPrimaryKey -> Rep TableHasPrimaryKey x Source #

to :: Rep TableHasPrimaryKey x -> TableHasPrimaryKey Source #

Generic PredicateSpecificity 
Instance details

Defined in Database.Beam.Migrate.Types.Predicates

Associated Types

type Rep PredicateSpecificity :: Type -> Type Source #

Methods

from :: PredicateSpecificity -> Rep PredicateSpecificity x Source #

to :: Rep PredicateSpecificity x -> PredicateSpecificity Source #

Generic SqliteExpressionSyntax 
Instance details

Defined in Database.Beam.Sqlite.Syntax

Associated Types

type Rep SqliteExpressionSyntax :: Type -> Type Source #

Methods

from :: SqliteExpressionSyntax -> Rep SqliteExpressionSyntax x Source #

to :: Rep SqliteExpressionSyntax x -> SqliteExpressionSyntax Source #

Generic SqliteDataTypeSyntax 
Instance details

Defined in Database.Beam.Sqlite.Syntax

Associated Types

type Rep SqliteDataTypeSyntax :: Type -> Type Source #

Methods

from :: SqliteDataTypeSyntax -> Rep SqliteDataTypeSyntax x Source #

to :: Rep SqliteDataTypeSyntax x -> SqliteDataTypeSyntax Source #

Generic SqliteColumnSchemaSyntax 
Instance details

Defined in Database.Beam.Sqlite.Syntax

Associated Types

type Rep SqliteColumnSchemaSyntax :: Type -> Type Source #

Methods

from :: SqliteColumnSchemaSyntax -> Rep SqliteColumnSchemaSyntax x Source #

to :: Rep SqliteColumnSchemaSyntax x -> SqliteColumnSchemaSyntax Source #

Generic SQLData 
Instance details

Defined in Database.SQLite3

Associated Types

type Rep SQLData :: Type -> Type Source #

Methods

from :: SQLData -> Rep SQLData x Source #

to :: Rep SQLData x -> SQLData Source #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type Source #

Methods

from :: URI -> Rep URI x Source #

to :: Rep URI x -> URI Source #

Generic ProposalBody 
Instance details

Defined in Cardano.Chain.Update.Proposal

Associated Types

type Rep ProposalBody :: Type -> Type Source #

Methods

from :: ProposalBody -> Rep ProposalBody x Source #

to :: Rep ProposalBody x -> ProposalBody Source #

Generic LovelacePortion 
Instance details

Defined in Cardano.Chain.Common.LovelacePortion

Associated Types

type Rep LovelacePortion :: Type -> Type Source #

Methods

from :: LovelacePortion -> Rep LovelacePortion x Source #

to :: Rep LovelacePortion x -> LovelacePortion Source #

Generic SoftforkRule 
Instance details

Defined in Cardano.Chain.Update.SoftforkRule

Associated Types

type Rep SoftforkRule :: Type -> Type Source #

Methods

from :: SoftforkRule -> Rep SoftforkRule x Source #

to :: Rep SoftforkRule x -> SoftforkRule Source #

Generic TxFeePolicy 
Instance details

Defined in Cardano.Chain.Common.TxFeePolicy

Associated Types

type Rep TxFeePolicy :: Type -> Type Source #

Methods

from :: TxFeePolicy -> Rep TxFeePolicy x Source #

to :: Rep TxFeePolicy x -> TxFeePolicy Source #

Generic SystemTag 
Instance details

Defined in Cardano.Chain.Update.SystemTag

Associated Types

type Rep SystemTag :: Type -> Type Source #

Methods

from :: SystemTag -> Rep SystemTag x Source #

to :: Rep SystemTag x -> SystemTag Source #

Generic InstallerHash 
Instance details

Defined in Cardano.Chain.Update.InstallerHash

Associated Types

type Rep InstallerHash :: Type -> Type Source #

Methods

from :: InstallerHash -> Rep InstallerHash x Source #

to :: Rep InstallerHash x -> InstallerHash Source #

Generic ProtocolParametersUpdate 
Instance details

Defined in Cardano.Chain.Update.ProtocolParametersUpdate

Associated Types

type Rep ProtocolParametersUpdate :: Type -> Type Source #

Methods

from :: ProtocolParametersUpdate -> Rep ProtocolParametersUpdate x Source #

to :: Rep ProtocolParametersUpdate x -> ProtocolParametersUpdate Source #

Generic BalancingError 
Instance details

Defined in Cardano.Node.Emulator.Internal.Node.Fee

Associated Types

type Rep BalancingError :: Type -> Type Source #

Methods

from :: BalancingError -> Rep BalancingError x Source #

to :: Rep BalancingError x -> BalancingError Source #

Generic EmulatorMsg 
Instance details

Defined in Cardano.Node.Emulator.LogMessages

Associated Types

type Rep EmulatorMsg :: Type -> Type Source #

Methods

from :: EmulatorMsg -> Rep EmulatorMsg x Source #

to :: Rep EmulatorMsg x -> EmulatorMsg Source #

Generic SQLError 
Instance details

Defined in Database.SQLite3

Associated Types

type Rep SQLError :: Type -> Type Source #

Methods

from :: SQLError -> Rep SQLError x Source #

to :: Rep SQLError x -> SQLError Source #

Generic Error 
Instance details

Defined in Database.SQLite3.Bindings.Types

Associated Types

type Rep Error :: Type -> Type Source #

Methods

from :: Error -> Rep Error x Source #

to :: Rep Error x -> Error Source #

Generic BeamError 
Instance details

Defined in Control.Monad.Freer.Extras.Beam.Common

Associated Types

type Rep BeamError :: Type -> Type Source #

Methods

from :: BeamError -> Rep BeamError x Source #

to :: Rep BeamError x -> BeamError Source #

Generic DbConfig 
Instance details

Defined in Control.Monad.Freer.Extras.Beam.Sqlite

Associated Types

type Rep DbConfig :: Type -> Type Source #

Methods

from :: DbConfig -> Rep DbConfig x Source #

to :: Rep DbConfig x -> DbConfig Source #

Generic Tool 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Tool :: Type -> Type Source #

Methods

from :: Tool -> Rep Tool x Source #

to :: Rep Tool x -> Tool Source #

Generic Form 
Instance details

Defined in Web.Internal.FormUrlEncoded

Associated Types

type Rep Form :: Type -> Type Source #

Methods

from :: Form -> Rep Form x Source #

to :: Rep Form x -> Form Source #

Generic Aggregated 
Instance details

Defined in Cardano.BM.Data.Aggregated

Associated Types

type Rep Aggregated :: Type -> Type Source #

Methods

from :: Aggregated -> Rep Aggregated x Source #

to :: Rep Aggregated x -> Aggregated Source #

Generic BaseStats 
Instance details

Defined in Cardano.BM.Data.Aggregated

Associated Types

type Rep BaseStats :: Type -> Type Source #

Methods

from :: BaseStats -> Rep BaseStats x Source #

to :: Rep BaseStats x -> BaseStats Source #

Generic EWMA 
Instance details

Defined in Cardano.BM.Data.Aggregated

Associated Types

type Rep EWMA :: Type -> Type Source #

Methods

from :: EWMA -> Rep EWMA x Source #

to :: Rep EWMA x -> EWMA Source #

Generic Stats 
Instance details

Defined in Cardano.BM.Data.Aggregated

Associated Types

type Rep Stats :: Type -> Type Source #

Methods

from :: Stats -> Rep Stats x Source #

to :: Rep Stats x -> Stats Source #

Generic AggregatedKind 
Instance details

Defined in Cardano.BM.Data.AggregatedKind

Associated Types

type Rep AggregatedKind :: Type -> Type Source #

Methods

from :: AggregatedKind -> Rep AggregatedKind x Source #

to :: Rep AggregatedKind x -> AggregatedKind Source #

Generic Endpoint 
Instance details

Defined in Cardano.BM.Data.Configuration

Associated Types

type Rep Endpoint :: Type -> Type Source #

Methods

from :: Endpoint -> Rep Endpoint x Source #

to :: Rep Endpoint x -> Endpoint Source #

Generic RemoteAddr 
Instance details

Defined in Cardano.BM.Data.Configuration

Associated Types

type Rep RemoteAddr :: Type -> Type Source #

Methods

from :: RemoteAddr -> Rep RemoteAddr x Source #

to :: Rep RemoteAddr x -> RemoteAddr Source #

Generic RemoteAddrNamed 
Instance details

Defined in Cardano.BM.Data.Configuration

Associated Types

type Rep RemoteAddrNamed :: Type -> Type Source #

Methods

from :: RemoteAddrNamed -> Rep RemoteAddrNamed x Source #

to :: Rep RemoteAddrNamed x -> RemoteAddrNamed Source #

Generic Representation 
Instance details

Defined in Cardano.BM.Data.Configuration

Associated Types

type Rep Representation :: Type -> Type Source #

Methods

from :: Representation -> Rep Representation x Source #

to :: Rep Representation x -> Representation Source #

Generic RotationParameters 
Instance details

Defined in Cardano.BM.Data.Rotation

Associated Types

type Rep RotationParameters :: Type -> Type Source #

Methods

from :: RotationParameters -> Rep RotationParameters x Source #

to :: Rep RotationParameters x -> RotationParameters Source #

Generic ScribeDefinition 
Instance details

Defined in Cardano.BM.Data.Output

Associated Types

type Rep ScribeDefinition :: Type -> Type Source #

Methods

from :: ScribeDefinition -> Rep ScribeDefinition x Source #

to :: Rep ScribeDefinition x -> ScribeDefinition Source #

Generic ScribeKind 
Instance details

Defined in Cardano.BM.Data.Output

Associated Types

type Rep ScribeKind :: Type -> Type Source #

Methods

from :: ScribeKind -> Rep ScribeKind x Source #

to :: Rep ScribeKind x -> ScribeKind Source #

Generic ScribeFormat 
Instance details

Defined in Cardano.BM.Data.Output

Associated Types

type Rep ScribeFormat :: Type -> Type Source #

Methods

from :: ScribeFormat -> Rep ScribeFormat x Source #

to :: Rep ScribeFormat x -> ScribeFormat Source #

Generic ScribePrivacy 
Instance details

Defined in Cardano.BM.Data.Output

Associated Types

type Rep ScribePrivacy :: Type -> Type Source #

Methods

from :: ScribePrivacy -> Rep ScribePrivacy x Source #

to :: Rep ScribePrivacy x -> ScribePrivacy Source #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type Source #

Methods

from :: URIAuth -> Rep URIAuth x Source #

to :: Rep URIAuth x -> URIAuth Source #

Generic InsertUtxoFailed 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep InsertUtxoFailed :: Type -> Type Source #

Methods

from :: InsertUtxoFailed -> Rep InsertUtxoFailed x Source #

to :: Rep InsertUtxoFailed x -> InsertUtxoFailed Source #

Generic RollbackFailed 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep RollbackFailed :: Type -> Type Source #

Methods

from :: RollbackFailed -> Rep RollbackFailed x Source #

to :: Rep RollbackFailed x -> RollbackFailed Source #

Generic CheckpointStore 
Instance details

Defined in Plutus.Contract.Checkpoint

Associated Types

type Rep CheckpointStore :: Type -> Type Source #

Methods

from :: CheckpointStore -> Rep CheckpointStore x Source #

to :: Rep CheckpointStore x -> CheckpointStore Source #

Generic ActiveEndpoint 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep ActiveEndpoint :: Type -> Type Source #

Methods

from :: ActiveEndpoint -> Rep ActiveEndpoint x Source #

to :: Rep ActiveEndpoint x -> ActiveEndpoint Source #

Generic BalanceTxResponse 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep BalanceTxResponse :: Type -> Type Source #

Methods

from :: BalanceTxResponse -> Rep BalanceTxResponse x Source #

to :: Rep BalanceTxResponse x -> BalanceTxResponse Source #

Generic WriteBalancedTxResponse 
Instance details

Defined in Plutus.Contract.Effects

Associated Types

type Rep WriteBalancedTxResponse :: Type -> Type Source #

Methods

from :: WriteBalancedTxResponse -> Rep WriteBalancedTxResponse x Source #

to :: Rep WriteBalancedTxResponse x -> WriteBalancedTxResponse Source #

Generic MatchingError 
Instance details

Defined in Plutus.Contract.Error

Associated Types

type Rep MatchingError :: Type -> Type Source #

Methods

from :: MatchingError -> Rep MatchingError x Source #

to :: Rep MatchingError x -> MatchingError Source #

Generic MkTxLog 
Instance details

Defined in Plutus.Contract.Request

Associated Types

type Rep MkTxLog :: Type -> Type Source #

Methods

from :: MkTxLog -> Rep MkTxLog x Source #

to :: Rep MkTxLog x -> MkTxLog Source #

Generic Any 
Instance details

Defined in Plutus.Script.Utils.Typed

Associated Types

type Rep Any :: Type -> Type Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Generic DiffMilliSeconds 
Instance details

Defined in Plutus.V1.Ledger.Time

Associated Types

type Rep DiffMilliSeconds :: Type -> Type Source #

Methods

from :: DiffMilliSeconds -> Rep DiffMilliSeconds x Source #

to :: Rep DiffMilliSeconds x -> DiffMilliSeconds Source #

Generic IterationID 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep IterationID :: Type -> Type Source #

Methods

from :: IterationID -> Rep IterationID x Source #

to :: Rep IterationID x -> IterationID Source #

Generic RequestID 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep RequestID :: Type -> Type Source #

Methods

from :: RequestID -> Rep RequestID x Source #

to :: Rep RequestID x -> RequestID Source #

Generic ContractActivityStatus 
Instance details

Defined in Wallet.Types

Associated Types

type Rep ContractActivityStatus :: Type -> Type Source #

Methods

from :: ContractActivityStatus -> Rep ContractActivityStatus x Source #

to :: Rep ContractActivityStatus x -> ContractActivityStatus Source #

Generic Signature 
Instance details

Defined in Ledger.Crypto

Associated Types

type Rep Signature :: Type -> Type Source #

Methods

from :: Signature -> Rep Signature x Source #

to :: Rep Signature x -> Signature Source #

Generic XPub 
Instance details

Defined in Cardano.Crypto.Wallet

Associated Types

type Rep XPub :: Type -> Type Source #

Methods

from :: XPub -> Rep XPub x Source #

to :: Rep XPub x -> XPub Source #

Generic ScriptContext 
Instance details

Defined in Plutus.V2.Ledger.Contexts

Associated Types

type Rep ScriptContext :: Type -> Type Source #

Methods

from :: ScriptContext -> Rep ScriptContext x Source #

to :: Rep ScriptContext x -> ScriptContext Source #

Generic ScriptContext 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep ScriptContext :: Type -> Type Source #

Methods

from :: ScriptContext -> Rep ScriptContext x Source #

to :: Rep ScriptContext x -> ScriptContext Source #

Generic ValueSpentBalances 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep ValueSpentBalances :: Type -> Type Source #

Methods

from :: ValueSpentBalances -> Rep ValueSpentBalances x Source #

to :: Rep ValueSpentBalances x -> ValueSpentBalances Source #

Generic TxConstraint 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep TxConstraint :: Type -> Type Source #

Methods

from :: TxConstraint -> Rep TxConstraint x Source #

to :: Rep TxConstraint x -> TxConstraint Source #

Generic TxConstraintFuns 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep TxConstraintFuns :: Type -> Type Source #

Methods

from :: TxConstraintFuns -> Rep TxConstraintFuns x Source #

to :: Rep TxConstraintFuns x -> TxConstraintFuns Source #

Generic CaseStyle 
Instance details

Defined in Data.Text.Class

Associated Types

type Rep CaseStyle :: Type -> Type Source #

Methods

from :: CaseStyle -> Rep CaseStyle x Source #

to :: Rep CaseStyle x -> CaseStyle Source #

Generic CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionLevel :: Type -> Type Source #

Methods

from :: CompressionLevel -> Rep CompressionLevel x Source #

to :: Rep CompressionLevel x -> CompressionLevel Source #

Generic CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionStrategy :: Type -> Type Source #

Methods

from :: CompressionStrategy -> Rep CompressionStrategy x Source #

to :: Rep CompressionStrategy x -> CompressionStrategy Source #

Generic Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Format :: Type -> Type Source #

Methods

from :: Format -> Rep Format x Source #

to :: Rep Format x -> Format Source #

Generic MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep MemoryLevel :: Type -> Type Source #

Methods

from :: MemoryLevel -> Rep MemoryLevel x Source #

to :: Rep MemoryLevel x -> MemoryLevel Source #

Generic Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Method :: Type -> Type Source #

Methods

from :: Method -> Rep Method x Source #

to :: Rep Method x -> Method Source #

Generic WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep WindowBits :: Type -> Type Source #

Methods

from :: WindowBits -> Rep WindowBits x Source #

to :: Rep WindowBits x -> WindowBits Source #

Generic NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

Associated Types

type Rep NetworkMagic :: Type -> Type Source #

Methods

from :: NetworkMagic -> Rep NetworkMagic x Source #

to :: Rep NetworkMagic x -> NetworkMagic Source #

Generic AddrAttributes 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Associated Types

type Rep AddrAttributes :: Type -> Type Source #

Methods

from :: AddrAttributes -> Rep AddrAttributes x Source #

to :: Rep AddrAttributes x -> AddrAttributes Source #

Generic HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Associated Types

type Rep HDAddressPayload :: Type -> Type Source #

Methods

from :: HDAddressPayload -> Rep HDAddressPayload x Source #

to :: Rep HDAddressPayload x -> HDAddressPayload Source #

Generic Address' 
Instance details

Defined in Cardano.Chain.Common.Address

Associated Types

type Rep Address' :: Type -> Type Source #

Methods

from :: Address' -> Rep Address' x Source #

to :: Rep Address' x -> Address' Source #

Generic TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Associated Types

type Rep TxIn :: Type -> Type Source #

Methods

from :: TxIn -> Rep TxIn x Source #

to :: Rep TxIn x -> TxIn Source #

Generic CekUserError 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep CekUserError :: Type -> Type Source #

Methods

from :: CekUserError -> Rep CekUserError x Source #

to :: Rep CekUserError x -> CekUserError Source #

Generic TxIn 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxIn :: Type -> Type Source #

Methods

from :: TxIn -> Rep TxIn x Source #

to :: Rep TxIn x -> TxIn Source #

Generic TxInType 
Instance details

Defined in Plutus.V1.Ledger.Tx

Associated Types

type Rep TxInType :: Type -> Type Source #

Methods

from :: TxInType -> Rep TxInType x Source #

to :: Rep TxInType x -> TxInType Source #

Generic LangDepView 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Associated Types

type Rep LangDepView :: Type -> Type Source #

Methods

from :: LangDepView -> Rep LangDepView x Source #

to :: Rep LangDepView x -> LangDepView Source #

Generic CekMachineCosts 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Associated Types

type Rep CekMachineCosts :: Type -> Type Source #

Methods

from :: CekMachineCosts -> Rep CekMachineCosts x Source #

to :: Rep CekMachineCosts x -> CekMachineCosts Source #

Generic MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Associated Types

type Rep MempoolSizeAndCapacity :: Type -> Type Source #

Methods

from :: MempoolSizeAndCapacity -> Rep MempoolSizeAndCapacity x Source #

to :: Rep MempoolSizeAndCapacity x -> MempoolSizeAndCapacity Source #

Generic KESPeriod 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Associated Types

type Rep KESPeriod :: Type -> Type Source #

Methods

from :: KESPeriod -> Rep KESPeriod x Source #

to :: Rep KESPeriod x -> KESPeriod Source #

Generic SatInt 
Instance details

Defined in Data.SatInt

Associated Types

type Rep SatInt :: Type -> Type Source #

Methods

from :: SatInt -> Rep SatInt x Source #

to :: Rep SatInt x -> SatInt Source #

Generic CovLoc 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CovLoc :: Type -> Type Source #

Methods

from :: CovLoc -> Rep CovLoc x Source #

to :: Rep CovLoc x -> CovLoc Source #

Generic CoverageAnnotation 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CoverageAnnotation :: Type -> Type Source #

Methods

from :: CoverageAnnotation -> Rep CoverageAnnotation x Source #

to :: Rep CoverageAnnotation x -> CoverageAnnotation Source #

Generic CoverageIndex 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CoverageIndex :: Type -> Type Source #

Methods

from :: CoverageIndex -> Rep CoverageIndex x Source #

to :: Rep CoverageIndex x -> CoverageIndex Source #

Generic CoverageMetadata 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CoverageMetadata :: Type -> Type Source #

Methods

from :: CoverageMetadata -> Rep CoverageMetadata x Source #

to :: Rep CoverageMetadata x -> CoverageMetadata Source #

Generic CoverageReport 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep CoverageReport :: Type -> Type Source #

Methods

from :: CoverageReport -> Rep CoverageReport x Source #

to :: Rep CoverageReport x -> CoverageReport Source #

Generic Metadata 
Instance details

Defined in PlutusTx.Coverage

Associated Types

type Rep Metadata :: Type -> Type Source #

Methods

from :: Metadata -> Rep Metadata x Source #

to :: Rep Metadata x -> Metadata Source #

Generic CabalSpecVersion 
Instance details

Defined in Distribution.CabalSpecVersion

Associated Types

type Rep CabalSpecVersion :: Type -> Type Source #

Methods

from :: CabalSpecVersion -> Rep CabalSpecVersion x Source #

to :: Rep CabalSpecVersion x -> CabalSpecVersion Source #

Generic Structure 
Instance details

Defined in Distribution.Utils.Structured

Associated Types

type Rep Structure :: Type -> Type Source #

Methods

from :: Structure -> Rep Structure x Source #

to :: Rep Structure x -> Structure Source #

Generic PError 
Instance details

Defined in Distribution.Parsec.Error

Associated Types

type Rep PError :: Type -> Type Source #

Methods

from :: PError -> Rep PError x Source #

to :: Rep PError x -> PError Source #

Generic Position 
Instance details

Defined in Distribution.Parsec.Position

Associated Types

type Rep Position :: Type -> Type Source #

Methods

from :: Position -> Rep Position x Source #

to :: Rep Position x -> Position Source #

Generic PWarnType 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarnType :: Type -> Type Source #

Methods

from :: PWarnType -> Rep PWarnType x Source #

to :: Rep PWarnType x -> PWarnType Source #

Generic PWarning 
Instance details

Defined in Distribution.Parsec.Warning

Associated Types

type Rep PWarning :: Type -> Type Source #

Methods

from :: PWarning -> Rep PWarning x Source #

to :: Rep PWarning x -> PWarning Source #

Generic Arch 
Instance details

Defined in Distribution.System

Associated Types

type Rep Arch :: Type -> Type Source #

Methods

from :: Arch -> Rep Arch x Source #

to :: Rep Arch x -> Arch Source #

Generic OS 
Instance details

Defined in Distribution.System

Associated Types

type Rep OS :: Type -> Type Source #

Methods

from :: OS -> Rep OS x Source #

to :: Rep OS x -> OS Source #

Generic Platform 
Instance details

Defined in Distribution.System

Associated Types

type Rep Platform :: Type -> Type Source #

Methods

from :: Platform -> Rep Platform x Source #

to :: Rep Platform x -> Platform Source #

Generic AdjacencyIntMap 
Instance details

Defined in Algebra.Graph.AdjacencyIntMap

Associated Types

type Rep AdjacencyIntMap :: Type -> Type Source #

Methods

from :: AdjacencyIntMap -> Rep AdjacencyIntMap x Source #

to :: Rep AdjacencyIntMap x -> AdjacencyIntMap Source #

Generic Alphabet 
Instance details

Defined in Data.ByteString.Base58.Internal

Associated Types

type Rep Alphabet :: Type -> Type Source #

Methods

from :: Alphabet -> Rep Alphabet x Source #

to :: Rep Alphabet x -> Alphabet Source #

Generic ByteString64 
Instance details

Defined in Data.ByteString.Base64.Type

Associated Types

type Rep ByteString64 :: Type -> Type Source #

Methods

from :: ByteString64 -> Rep ByteString64 x Source #

to :: Rep ByteString64 x -> ByteString64 Source #

Generic MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep MIRPot :: Type -> Type Source #

Methods

from :: MIRPot -> Rep MIRPot x Source #

to :: Rep MIRPot x -> MIRPot Source #

Generic Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Url :: Type -> Type Source #

Methods

from :: Url -> Rep Url x Source #

to :: Rep Url x -> Url Source #

Generic SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep SignKey :: Type -> Type Source #

Methods

from :: SignKey -> Rep SignKey x Source #

to :: Rep SignKey x -> SignKey Source #

Generic VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep VerKey :: Type -> Type Source #

Methods

from :: VerKey -> Rep VerKey x Source #

to :: Rep VerKey x -> VerKey Source #

Generic TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Associated Types

type Rep TxInWitness :: Type -> Type Source #

Methods

from :: TxInWitness -> Rep TxInWitness x Source #

to :: Rep TxInWitness x -> TxInWitness Source #

Generic TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Associated Types

type Rep TxSigData :: Type -> Type Source #

Methods

from :: TxSigData -> Rep TxSigData x Source #

to :: Rep TxSigData x -> TxSigData Source #

Generic SignTag 
Instance details

Defined in Cardano.Crypto.Signing.Tag

Associated Types

type Rep SignTag :: Type -> Type Source #

Methods

from :: SignTag -> Rep SignTag x Source #

to :: Rep SignTag x -> SignTag Source #

Generic XPub 
Instance details

Defined in Cardano.Crypto.Wallet.Pure

Associated Types

type Rep XPub :: Type -> Type Source #

Methods

from :: XPub -> Rep XPub x Source #

to :: Rep XPub x -> XPub Source #

Generic Point 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Associated Types

type Rep Point :: Type -> Type Source #

Methods

from :: Point -> Rep Point x Source #

to :: Rep Point x -> Point Source #

Generic Output 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep Output :: Type -> Type Source #

Methods

from :: Output -> Rep Output x Source #

to :: Rep Output x -> Output Source #

Generic Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep Proof :: Type -> Type Source #

Methods

from :: Proof -> Rep Proof x Source #

to :: Rep Proof x -> Proof Source #

Generic RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

Associated Types

type Rep RedeemVerificationKey :: Type -> Type Source #

Methods

from :: RedeemVerificationKey -> Rep RedeemVerificationKey x Source #

to :: Rep RedeemVerificationKey x -> RedeemVerificationKey Source #

Generic RedeemSigningKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.SigningKey

Associated Types

type Rep RedeemSigningKey :: Type -> Type Source #

Methods

from :: RedeemSigningKey -> Rep RedeemSigningKey x Source #

to :: Rep RedeemSigningKey x -> RedeemSigningKey Source #

Generic ValidityInterval 
Instance details

Defined in Cardano.Ledger.ShelleyMA.Timelocks

Associated Types

type Rep ValidityInterval :: Type -> Type Source #

Methods

from :: ValidityInterval -> Rep ValidityInterval x Source #

to :: Rep ValidityInterval x -> ValidityInterval Source #

Generic ScriptResult 
Instance details

Defined in Cardano.Ledger.Alonzo.TxInfo

Associated Types

type Rep ScriptResult :: Type -> Type Source #

Methods

from :: ScriptResult -> Rep ScriptResult x Source #

to :: Rep ScriptResult x -> ScriptResult Source #

Generic FailureDescription 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxos

Associated Types

type Rep FailureDescription :: Type -> Type Source #

Methods

from :: FailureDescription -> Rep FailureDescription x Source #

to :: Rep FailureDescription x -> FailureDescription Source #

Generic TagMismatchDescription 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxos

Associated Types

type Rep TagMismatchDescription :: Type -> Type Source #

Methods

from :: TagMismatchDescription -> Rep TagMismatchDescription x Source #

to :: Rep TagMismatchDescription x -> TagMismatchDescription Source #

Generic PlutusDebug 
Instance details

Defined in Cardano.Ledger.Alonzo.TxInfo

Associated Types

type Rep PlutusDebug :: Type -> Type Source #

Methods

from :: PlutusDebug -> Rep PlutusDebug x Source #

to :: Rep PlutusDebug x -> PlutusDebug Source #

Generic ScriptFailure 
Instance details

Defined in Cardano.Ledger.Alonzo.TxInfo

Associated Types

type Rep ScriptFailure :: Type -> Type Source #

Methods

from :: ScriptFailure -> Rep ScriptFailure x Source #

to :: Rep ScriptFailure x -> ScriptFailure Source #

Generic Tag 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep Tag :: Type -> Type Source #

Methods

from :: Tag -> Rep Tag x Source #

to :: Rep Tag x -> Tag Source #

Generic EvaluationContext 
Instance details

Defined in Plutus.ApiCommon

Associated Types

type Rep EvaluationContext :: Type -> Type Source #

Methods

from :: EvaluationContext -> Rep EvaluationContext x Source #

to :: Rep EvaluationContext x -> EvaluationContext Source #

Generic TxInInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep TxInInfo :: Type -> Type Source #

Methods

from :: TxInInfo -> Rep TxInInfo x Source #

to :: Rep TxInInfo x -> TxInInfo Source #

Generic TxInfo 
Instance details

Defined in Plutus.V1.Ledger.Contexts

Associated Types

type Rep TxInfo :: Type -> Type Source #

Methods

from :: TxInfo -> Rep TxInfo x Source #

to :: Rep TxInfo x -> TxInfo Source #

Generic TxInfo 
Instance details

Defined in Plutus.V2.Ledger.Contexts

Associated Types

type Rep TxInfo :: Type -> Type Source #

Methods

from :: TxInfo -> Rep TxInfo x Source #

to :: Rep TxInfo x -> TxInfo Source #

Generic ChainDifficulty 
Instance details

Defined in Cardano.Chain.Common.ChainDifficulty

Associated Types

type Rep ChainDifficulty :: Type -> Type Source #

Methods

from :: ChainDifficulty -> Rep ChainDifficulty x Source #

to :: Rep ChainDifficulty x -> ChainDifficulty Source #

Generic Proof 
Instance details

Defined in Cardano.Chain.Block.Proof

Associated Types

type Rep Proof :: Type -> Type Source #

Methods

from :: Proof -> Rep Proof x Source #

to :: Rep Proof x -> Proof Source #

Generic SscPayload 
Instance details

Defined in Cardano.Chain.Ssc

Associated Types

type Rep SscPayload :: Type -> Type Source #

Methods

from :: SscPayload -> Rep SscPayload x Source #

to :: Rep SscPayload x -> SscPayload Source #

Generic EpochAndSlotCount 
Instance details

Defined in Cardano.Chain.Slotting.EpochAndSlotCount

Associated Types

type Rep EpochAndSlotCount :: Type -> Type Source #

Methods

from :: EpochAndSlotCount -> Rep EpochAndSlotCount x Source #

to :: Rep EpochAndSlotCount x -> EpochAndSlotCount Source #

Generic TxProof 
Instance details

Defined in Cardano.Chain.UTxO.TxProof

Associated Types

type Rep TxProof :: Type -> Type Source #

Methods

from :: TxProof -> Rep TxProof x Source #

to :: Rep TxProof x -> TxProof Source #

Generic SscProof 
Instance details

Defined in Cardano.Chain.Ssc

Associated Types

type Rep SscProof :: Type -> Type Source #

Methods

from :: SscProof -> Rep SscProof x Source #

to :: Rep SscProof x -> SscProof Source #

Generic CompactTxIn 
Instance details

Defined in Cardano.Chain.UTxO.Compact

Associated Types

type Rep CompactTxIn :: Type -> Type Source #

Methods

from :: CompactTxIn -> Rep CompactTxIn x Source #

to :: Rep CompactTxIn x -> CompactTxIn Source #

Generic CompactTxOut 
Instance details

Defined in Cardano.Chain.UTxO.Compact

Associated Types

type Rep CompactTxOut :: Type -> Type Source #

Methods

from :: CompactTxOut -> Rep CompactTxOut x Source #

to :: Rep CompactTxOut x -> CompactTxOut Source #

Generic State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Interface

Associated Types

type Rep State :: Type -> Type Source #

Methods

from :: State -> Rep State x Source #

to :: Rep State x -> State Source #

Generic BlockCount 
Instance details

Defined in Cardano.Chain.Common.BlockCount

Associated Types

type Rep BlockCount :: Type -> Type Source #

Methods

from :: BlockCount -> Rep BlockCount x Source #

to :: Rep BlockCount x -> BlockCount Source #

Generic UTxOConfiguration 
Instance details

Defined in Cardano.Chain.UTxO.UTxOConfiguration

Associated Types

type Rep UTxOConfiguration :: Type -> Type Source #

Methods

from :: UTxOConfiguration -> Rep UTxOConfiguration x Source #

to :: Rep UTxOConfiguration x -> UTxOConfiguration Source #

Generic ApplicationName 
Instance details

Defined in Cardano.Chain.Update.ApplicationName

Associated Types

type Rep ApplicationName :: Type -> Type Source #

Methods

from :: ApplicationName -> Rep ApplicationName x Source #

to :: Rep ApplicationName x -> ApplicationName Source #

Generic ApplicationVersion 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Associated Types

type Rep ApplicationVersion :: Type -> Type Source #

Methods

from :: ApplicationVersion -> Rep ApplicationVersion x Source #

to :: Rep ApplicationVersion x -> ApplicationVersion Source #

Generic ProtocolUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Associated Types

type Rep ProtocolUpdateProposal :: Type -> Type Source #

Methods

from :: ProtocolUpdateProposal -> Rep ProtocolUpdateProposal x Source #

to :: Rep ProtocolUpdateProposal x -> ProtocolUpdateProposal Source #

Generic SoftwareUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Associated Types

type Rep SoftwareUpdateProposal :: Type -> Type Source #

Methods

from :: SoftwareUpdateProposal -> Rep SoftwareUpdateProposal x Source #

to :: Rep SoftwareUpdateProposal x -> SoftwareUpdateProposal Source #

Generic UnparsedFields 
Instance details

Defined in Cardano.Chain.Common.Attributes

Associated Types

type Rep UnparsedFields :: Type -> Type Source #

Methods

from :: UnparsedFields -> Rep UnparsedFields x Source #

to :: Rep UnparsedFields x -> UnparsedFields Source #

Generic AddrSpendingData 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Associated Types

type Rep AddrSpendingData :: Type -> Type Source #

Methods

from :: AddrSpendingData -> Rep AddrSpendingData x Source #

to :: Rep AddrSpendingData x -> AddrSpendingData Source #

Generic AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Associated Types

type Rep AddrType :: Type -> Type Source #

Methods

from :: AddrType -> Rep AddrType x Source #

to :: Rep AddrType x -> AddrType Source #

Generic TxSizeLinear 
Instance details

Defined in Cardano.Chain.Common.TxSizeLinear

Associated Types

type Rep TxSizeLinear :: Type -> Type Source #

Methods

from :: TxSizeLinear -> Rep TxSizeLinear x Source #

to :: Rep TxSizeLinear x -> TxSizeLinear Source #

Generic State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Activation

Associated Types

type Rep State :: Type -> Type Source #

Methods

from :: State -> Rep State x Source #

to :: Rep State x -> State Source #

Generic Environment 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Interface

Associated Types

type Rep Environment :: Type -> Type Source #

Methods

from :: Environment -> Rep Environment x Source #

to :: Rep Environment x -> Environment Source #

Generic State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

Associated Types

type Rep State :: Type -> Type Source #

Methods

from :: State -> Rep State x Source #

to :: Rep State x -> State Source #

Generic Environment 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

Associated Types

type Rep Environment :: Type -> Type Source #

Methods

from :: Environment -> Rep Environment x Source #

to :: Rep Environment x -> Environment Source #

Generic GenesisData 
Instance details

Defined in Cardano.Chain.Genesis.Data

Associated Types

type Rep GenesisData :: Type -> Type Source #

Methods

from :: GenesisData -> Rep GenesisData x Source #

to :: Rep GenesisData x -> GenesisData Source #

Generic SlotCount 
Instance details

Defined in Cardano.Chain.Slotting.SlotCount

Associated Types

type Rep SlotCount :: Type -> Type Source #

Methods

from :: SlotCount -> Rep SlotCount x Source #

to :: Rep SlotCount x -> SlotCount Source #

Generic GeneratedSecrets 
Instance details

Defined in Cardano.Chain.Genesis.Generate

Associated Types

type Rep GeneratedSecrets :: Type -> Type Source #

Methods

from :: GeneratedSecrets -> Rep GeneratedSecrets x Source #

to :: Rep GeneratedSecrets x -> GeneratedSecrets Source #

Generic PoorSecret 
Instance details

Defined in Cardano.Chain.Genesis.Generate

Associated Types

type Rep PoorSecret :: Type -> Type Source #

Methods

from :: PoorSecret -> Rep PoorSecret x Source #

to :: Rep PoorSecret x -> PoorSecret Source #

Generic GenesisSpec 
Instance details

Defined in Cardano.Chain.Genesis.Spec

Associated Types

type Rep GenesisSpec :: Type -> Type Source #

Methods

from :: GenesisSpec -> Rep GenesisSpec x Source #

to :: Rep GenesisSpec x -> GenesisSpec Source #

Generic FakeAvvmOptions 
Instance details

Defined in Cardano.Chain.Genesis.Initializer

Associated Types

type Rep FakeAvvmOptions :: Type -> Type Source #

Methods

from :: FakeAvvmOptions -> Rep FakeAvvmOptions x Source #

to :: Rep FakeAvvmOptions x -> FakeAvvmOptions Source #

Generic CompactTxId 
Instance details

Defined in Cardano.Chain.UTxO.Compact

Associated Types

type Rep CompactTxId :: Type -> Type Source #

Methods

from :: CompactTxId -> Rep CompactTxId x Source #

to :: Rep CompactTxId x -> CompactTxId Source #

Generic TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Associated Types

type Rep TxOut :: Type -> Type Source #

Methods

from :: TxOut -> Rep TxOut x Source #

to :: Rep TxOut x -> TxOut Source #

Generic Environment 
Instance details

Defined in Cardano.Chain.Update.Validation.Voting

Associated Types

type Rep Environment :: Type -> Type Source #

Methods

from :: Environment -> Rep Environment x Source #

to :: Rep Environment x -> Environment Source #

Generic RegistrationEnvironment 
Instance details

Defined in Cardano.Chain.Update.Validation.Voting

Associated Types

type Rep RegistrationEnvironment :: Type -> Type Source #

Methods

from :: RegistrationEnvironment -> Rep RegistrationEnvironment x Source #

to :: Rep RegistrationEnvironment x -> RegistrationEnvironment Source #

Generic ActiveSlotCoeff 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep ActiveSlotCoeff :: Type -> Type Source #

Methods

from :: ActiveSlotCoeff -> Rep ActiveSlotCoeff x Source #

to :: Rep ActiveSlotCoeff x -> ActiveSlotCoeff Source #

Generic DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep DnsName :: Type -> Type Source #

Methods

from :: DnsName -> Rep DnsName x Source #

to :: Rep DnsName x -> DnsName Source #

Generic Port 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Port :: Type -> Type Source #

Methods

from :: Port -> Rep Port x Source #

to :: Rep Port x -> Port Source #

Generic PositiveInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep PositiveInterval :: Type -> Type Source #

Methods

from :: PositiveInterval -> Rep PositiveInterval x Source #

to :: Rep PositiveInterval x -> PositiveInterval Source #

Generic Seed 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Seed :: Type -> Type Source #

Methods

from :: Seed -> Rep Seed x Source #

to :: Rep Seed x -> Seed Source #

Generic Duration 
Instance details

Defined in Cardano.Ledger.Slot

Associated Types

type Rep Duration :: Type -> Type Source #

Methods

from :: Duration -> Rep Duration x Source #

to :: Rep Duration x -> Duration Source #

Generic ChainChecksPParams 
Instance details

Defined in Cardano.Ledger.Chain

Associated Types

type Rep ChainChecksPParams :: Type -> Type Source #

Methods

from :: ChainChecksPParams -> Rep ChainChecksPParams x Source #

to :: Rep ChainChecksPParams x -> ChainChecksPParams Source #

Generic ChainCode 
Instance details

Defined in Cardano.Ledger.Shelley.Address.Bootstrap

Associated Types

type Rep ChainCode :: Type -> Type Source #

Methods

from :: ChainCode -> Rep ChainCode x Source #

to :: Rep ChainCode x -> ChainCode Source #

Generic Histogram 
Instance details

Defined in Cardano.Ledger.Shelley.PoolRank

Associated Types

type Rep Histogram :: Type -> Type Source #

Methods

from :: Histogram -> Rep Histogram x Source #

to :: Rep Histogram x -> Histogram Source #

Generic PerformanceEstimate 
Instance details

Defined in Cardano.Ledger.Shelley.PoolRank

Associated Types

type Rep PerformanceEstimate :: Type -> Type Source #

Methods

from :: PerformanceEstimate -> Rep PerformanceEstimate x Source #

to :: Rep PerformanceEstimate x -> PerformanceEstimate Source #

Generic StakeShare 
Instance details

Defined in Cardano.Ledger.Shelley.Rewards

Associated Types

type Rep StakeShare :: Type -> Type Source #

Methods

from :: StakeShare -> Rep StakeShare x Source #

to :: Rep StakeShare x -> StakeShare Source #

Generic VotingPeriod 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

Associated Types

type Rep VotingPeriod :: Type -> Type Source #

Methods

from :: VotingPeriod -> Rep VotingPeriod x Source #

to :: Rep VotingPeriod x -> VotingPeriod Source #

Generic TicknState 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Tickn

Associated Types

type Rep TicknState :: Type -> Type Source #

Methods

from :: TicknState -> Rep TicknState x Source #

to :: Rep TicknState x -> TicknState Source #

Generic TicknPredicateFailure 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Tickn

Associated Types

type Rep TicknPredicateFailure :: Type -> Type Source #

Methods

from :: TicknPredicateFailure -> Rep TicknPredicateFailure x Source #

to :: Rep TicknPredicateFailure x -> TicknPredicateFailure Source #

Generic Filler 
Instance details

Defined in Flat.Filler

Associated Types

type Rep Filler :: Type -> Type Source #

Methods

from :: Filler -> Rep Filler x Source #

to :: Rep Filler x -> Filler Source #

Generic ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Associated Types

type Rep ClosureType :: Type -> Type Source #

Methods

from :: ClosureType -> Rep ClosureType x Source #

to :: Rep ClosureType x -> ClosureType Source #

Generic PrimType 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimType :: Type -> Type Source #

Methods

from :: PrimType -> Rep PrimType x Source #

to :: Rep PrimType x -> PrimType Source #

Generic StgInfoTable 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Associated Types

type Rep StgInfoTable :: Type -> Type Source #

Methods

from :: StgInfoTable -> Rep StgInfoTable x Source #

to :: Rep StgInfoTable x -> StgInfoTable Source #

Generic Half 
Instance details

Defined in Numeric.Half.Internal

Associated Types

type Rep Half :: Type -> Type Source #

Methods

from :: Half -> Rep Half x Source #

to :: Rep Half x -> Half Source #

Generic IP 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IP :: Type -> Type Source #

Methods

from :: IP -> Rep IP x Source #

to :: Rep IP x -> IP Source #

Generic IPRange 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep IPRange :: Type -> Type Source #

Methods

from :: IPRange -> Rep IPRange x Source #

to :: Rep IPRange x -> IPRange Source #

Generic NewtonParam 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep NewtonParam :: Type -> Type Source #

Methods

from :: NewtonParam -> Rep NewtonParam x Source #

to :: Rep NewtonParam x -> NewtonParam Source #

Generic NewtonStep 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep NewtonStep :: Type -> Type Source #

Methods

from :: NewtonStep -> Rep NewtonStep x Source #

to :: Rep NewtonStep x -> NewtonStep Source #

Generic RiddersParam 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep RiddersParam :: Type -> Type Source #

Methods

from :: RiddersParam -> Rep RiddersParam x Source #

to :: Rep RiddersParam x -> RiddersParam Source #

Generic RiddersStep 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep RiddersStep :: Type -> Type Source #

Methods

from :: RiddersStep -> Rep RiddersStep x Source #

to :: Rep RiddersStep x -> RiddersStep Source #

Generic Tolerance 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep Tolerance :: Type -> Type Source #

Methods

from :: Tolerance -> Rep Tolerance x Source #

to :: Rep Tolerance x -> Tolerance Source #

Generic Pos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep Pos :: Type -> Type Source #

Methods

from :: Pos -> Rep Pos x Source #

to :: Rep Pos x -> Pos Source #

Generic InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosException :: Type -> Type Source #

Methods

from :: InvalidPosException -> Rep InvalidPosException x Source #

to :: Rep InvalidPosException x -> InvalidPosException Source #

Generic MuxError 
Instance details

Defined in Network.Mux.Trace

Associated Types

type Rep MuxError :: Type -> Type Source #

Methods

from :: MuxError -> Rep MuxError x Source #

to :: Rep MuxError x -> MuxError Source #

Generic SDUSize 
Instance details

Defined in Network.Mux.Types

Associated Types

type Rep SDUSize :: Type -> Type Source #

Methods

from :: SDUSize -> Rep SDUSize x Source #

to :: Rep SDUSize x -> SDUSize Source #

Generic IsEBB 
Instance details

Defined in Ouroboros.Consensus.Block.EBB

Associated Types

type Rep IsEBB :: Type -> Type Source #

Methods

from :: IsEBB -> Rep IsEBB x Source #

to :: Rep IsEBB x -> IsEBB Source #

Generic CurrentSlot 
Instance details

Defined in Ouroboros.Consensus.BlockchainTime.API

Associated Types

type Rep CurrentSlot :: Type -> Type Source #

Methods

from :: CurrentSlot -> Rep CurrentSlot x Source #

to :: Rep CurrentSlot x -> CurrentSlot Source #

Generic EraMismatch 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Associated Types

type Rep EraMismatch :: Type -> Type Source #

Methods

from :: EraMismatch -> Rep EraMismatch x Source #

to :: Rep EraMismatch x -> EraMismatch Source #

Generic SafeZone 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.EraParams

Associated Types

type Rep SafeZone :: Type -> Type Source #

Methods

from :: SafeZone -> Rep SafeZone x Source #

to :: Rep SafeZone x -> SafeZone Source #

Generic EpochInEra 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Associated Types

type Rep EpochInEra :: Type -> Type Source #

Methods

from :: EpochInEra -> Rep EpochInEra x Source #

to :: Rep EpochInEra x -> EpochInEra Source #

Generic SlotInEpoch 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Associated Types

type Rep SlotInEpoch :: Type -> Type Source #

Methods

from :: SlotInEpoch -> Rep SlotInEpoch x Source #

to :: Rep SlotInEpoch x -> SlotInEpoch Source #

Generic SlotInEra 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Associated Types

type Rep SlotInEra :: Type -> Type Source #

Methods

from :: SlotInEra -> Rep SlotInEra x Source #

to :: Rep SlotInEra x -> SlotInEra Source #

Generic TimeInEra 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Associated Types

type Rep TimeInEra :: Type -> Type Source #

Methods

from :: TimeInEra -> Rep TimeInEra x Source #

to :: Rep TimeInEra x -> TimeInEra Source #

Generic TimeInSlot 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Associated Types

type Rep TimeInSlot :: Type -> Type Source #

Methods

from :: TimeInSlot -> Rep TimeInSlot x Source #

to :: Rep TimeInSlot x -> TimeInSlot Source #

Generic EraEnd 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

Associated Types

type Rep EraEnd :: Type -> Type Source #

Methods

from :: EraEnd -> Rep EraEnd x Source #

to :: Rep EraEnd x -> EraEnd Source #

Generic NodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

Associated Types

type Rep NodeId :: Type -> Type Source #

Methods

from :: NodeId -> Rep NodeId x Source #

to :: Rep NodeId x -> NodeId Source #

Generic PBftParams 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftParams :: Type -> Type Source #

Methods

from :: PBftParams -> Rep PBftParams x Source #

to :: Rep PBftParams x -> PBftParams Source #

Generic PBftMockVerKeyHash 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Associated Types

type Rep PBftMockVerKeyHash :: Type -> Type Source #

Methods

from :: PBftMockVerKeyHash -> Rep PBftMockVerKeyHash x Source #

to :: Rep PBftMockVerKeyHash x -> PBftMockVerKeyHash Source #

Generic ChainType 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

Associated Types

type Rep ChainType :: Type -> Type Source #

Methods

from :: ChainType -> Rep ChainType x Source #

to :: Rep ChainType x -> ChainType Source #

Generic MaxSlotNo 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep MaxSlotNo :: Type -> Type Source #

Methods

from :: MaxSlotNo -> Rep MaxSlotNo x Source #

to :: Rep MaxSlotNo x -> MaxSlotNo Source #

Generic ScheduledGc 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Background

Associated Types

type Rep ScheduledGc :: Type -> Type Source #

Methods

from :: ScheduledGc -> Rep ScheduledGc x Source #

to :: Rep ScheduledGc x -> ScheduledGc Source #

Generic DiskSnapshot 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.OnDisk

Associated Types

type Rep DiskSnapshot :: Type -> Type Source #

Methods

from :: DiskSnapshot -> Rep DiskSnapshot x Source #

to :: Rep DiskSnapshot x -> DiskSnapshot Source #

Generic ChunkNo 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal

Associated Types

type Rep ChunkNo :: Type -> Type Source #

Methods

from :: ChunkNo -> Rep ChunkNo x Source #

to :: Rep ChunkNo x -> ChunkNo Source #

Generic CRC 
Instance details

Defined in Ouroboros.Consensus.Storage.FS.CRC

Associated Types

type Rep CRC :: Type -> Type Source #

Methods

from :: CRC -> Rep CRC x Source #

to :: Rep CRC x -> CRC Source #

Generic ChunkSize 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal

Associated Types

type Rep ChunkSize :: Type -> Type Source #

Methods

from :: ChunkSize -> Rep ChunkSize x Source #

to :: Rep ChunkSize x -> ChunkSize Source #

Generic RelativeSlot 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal

Associated Types

type Rep RelativeSlot :: Type -> Type Source #

Methods

from :: RelativeSlot -> Rep RelativeSlot x Source #

to :: Rep RelativeSlot x -> RelativeSlot Source #

Generic ChunkSlot 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Layout

Associated Types

type Rep ChunkSlot :: Type -> Type Source #

Methods

from :: ChunkSlot -> Rep ChunkSlot x Source #

to :: Rep ChunkSlot x -> ChunkSlot Source #

Generic BlockOrEBB 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep BlockOrEBB :: Type -> Type Source #

Methods

from :: BlockOrEBB -> Rep BlockOrEBB x Source #

to :: Rep BlockOrEBB x -> BlockOrEBB Source #

Generic PrimaryIndex 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Primary

Associated Types

type Rep PrimaryIndex :: Type -> Type Source #

Methods

from :: PrimaryIndex -> Rep PrimaryIndex x Source #

to :: Rep PrimaryIndex x -> PrimaryIndex Source #

Generic TraceCacheEvent 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep TraceCacheEvent :: Type -> Type Source #

Methods

from :: TraceCacheEvent -> Rep TraceCacheEvent x Source #

to :: Rep TraceCacheEvent x -> TraceCacheEvent Source #

Generic BlockSize 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

Associated Types

type Rep BlockSize :: Type -> Type Source #

Methods

from :: BlockSize -> Rep BlockSize x Source #

to :: Rep BlockSize x -> BlockSize Source #

Generic ValidationPolicy 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep ValidationPolicy :: Type -> Type Source #

Methods

from :: ValidationPolicy -> Rep ValidationPolicy x Source #

to :: Rep ValidationPolicy x -> ValidationPolicy Source #

Generic SnapshotInterval 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy

Associated Types

type Rep SnapshotInterval :: Type -> Type Source #

Methods

from :: SnapshotInterval -> Rep SnapshotInterval x Source #

to :: Rep SnapshotInterval x -> SnapshotInterval Source #

Generic BlocksPerFile 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep BlocksPerFile :: Type -> Type Source #

Methods

from :: BlocksPerFile -> Rep BlocksPerFile x Source #

to :: Rep BlocksPerFile x -> BlocksPerFile Source #

Generic BlockOffset 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep BlockOffset :: Type -> Type Source #

Methods

from :: BlockOffset -> Rep BlockOffset x Source #

to :: Rep BlockOffset x -> BlockOffset Source #

Generic BlockSize 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep BlockSize :: Type -> Type Source #

Methods

from :: BlockSize -> Rep BlockSize x Source #

to :: Rep BlockSize x -> BlockSize Source #

Generic Appender 
Instance details

Defined in Ouroboros.Consensus.Util.MonadSTM.RAWLock

Associated Types

type Rep Appender :: Type -> Type Source #

Methods

from :: Appender -> Rep Appender x Source #

to :: Rep Appender x -> Appender Source #

Generic RegistryStatus 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Associated Types

type Rep RegistryStatus :: Type -> Type Source #

Methods

from :: RegistryStatus -> Rep RegistryStatus x Source #

to :: Rep RegistryStatus x -> RegistryStatus Source #

Generic Fingerprint 
Instance details

Defined in Ouroboros.Consensus.Util.STM

Associated Types

type Rep Fingerprint :: Type -> Type Source #

Methods

from :: Fingerprint -> Rep Fingerprint x Source #

to :: Rep Fingerprint x -> Fingerprint Source #

Generic InputVRF 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.VRF

Associated Types

type Rep InputVRF :: Type -> Type Source #

Methods

from :: InputVRF -> Rep InputVRF x Source #

to :: Rep InputVRF x -> InputVRF Source #

Generic PeerAdvertise 
Instance details

Defined in Ouroboros.Network.PeerSelection.Types

Associated Types

type Rep PeerAdvertise :: Type -> Type Source #

Methods

from :: PeerAdvertise -> Rep PeerAdvertise x Source #

to :: Rep PeerAdvertise x -> PeerAdvertise Source #

Generic FileDescriptor 
Instance details

Defined in Ouroboros.Network.Snocket

Associated Types

type Rep FileDescriptor :: Type -> Type Source #

Methods

from :: FileDescriptor -> Rep FileDescriptor x Source #

to :: Rep FileDescriptor x -> FileDescriptor Source #

Generic LocalAddress 
Instance details

Defined in Ouroboros.Network.Snocket

Associated Types

type Rep LocalAddress :: Type -> Type Source #

Methods

from :: LocalAddress -> Rep LocalAddress x Source #

to :: Rep LocalAddress x -> LocalAddress Source #

Generic LocalSocket 
Instance details

Defined in Ouroboros.Network.Snocket

Associated Types

type Rep LocalSocket :: Type -> Type Source #

Methods

from :: LocalSocket -> Rep LocalSocket x Source #

to :: Rep LocalSocket x -> LocalSocket Source #

Generic ModelAddedSizes 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelAddedSizes :: Type -> Type Source #

Methods

from :: ModelAddedSizes -> Rep ModelAddedSizes x Source #

to :: Rep ModelAddedSizes x -> ModelAddedSizes Source #

Generic ModelConstantOrLinear 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelConstantOrLinear :: Type -> Type Source #

Methods

from :: ModelConstantOrLinear -> Rep ModelConstantOrLinear x Source #

to :: Rep ModelConstantOrLinear x -> ModelConstantOrLinear Source #

Generic ModelConstantOrTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelConstantOrTwoArguments :: Type -> Type Source #

Methods

from :: ModelConstantOrTwoArguments -> Rep ModelConstantOrTwoArguments x Source #

to :: Rep ModelConstantOrTwoArguments x -> ModelConstantOrTwoArguments Source #

Generic ModelFiveArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelFiveArguments :: Type -> Type Source #

Methods

from :: ModelFiveArguments -> Rep ModelFiveArguments x Source #

to :: Rep ModelFiveArguments x -> ModelFiveArguments Source #

Generic ModelFourArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelFourArguments :: Type -> Type Source #

Methods

from :: ModelFourArguments -> Rep ModelFourArguments x Source #

to :: Rep ModelFourArguments x -> ModelFourArguments Source #

Generic ModelLinearSize 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelLinearSize :: Type -> Type Source #

Methods

from :: ModelLinearSize -> Rep ModelLinearSize x Source #

to :: Rep ModelLinearSize x -> ModelLinearSize Source #

Generic ModelMaxSize 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelMaxSize :: Type -> Type Source #

Methods

from :: ModelMaxSize -> Rep ModelMaxSize x Source #

to :: Rep ModelMaxSize x -> ModelMaxSize Source #

Generic ModelMinSize 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelMinSize :: Type -> Type Source #

Methods

from :: ModelMinSize -> Rep ModelMinSize x Source #

to :: Rep ModelMinSize x -> ModelMinSize Source #

Generic ModelMultipliedSizes 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelMultipliedSizes :: Type -> Type Source #

Methods

from :: ModelMultipliedSizes -> Rep ModelMultipliedSizes x Source #

to :: Rep ModelMultipliedSizes x -> ModelMultipliedSizes Source #

Generic ModelOneArgument 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelOneArgument :: Type -> Type Source #

Methods

from :: ModelOneArgument -> Rep ModelOneArgument x Source #

to :: Rep ModelOneArgument x -> ModelOneArgument Source #

Generic ModelSixArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelSixArguments :: Type -> Type Source #

Methods

from :: ModelSixArguments -> Rep ModelSixArguments x Source #

to :: Rep ModelSixArguments x -> ModelSixArguments Source #

Generic ModelSubtractedSizes 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelSubtractedSizes :: Type -> Type Source #

Methods

from :: ModelSubtractedSizes -> Rep ModelSubtractedSizes x Source #

to :: Rep ModelSubtractedSizes x -> ModelSubtractedSizes Source #

Generic ModelThreeArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelThreeArguments :: Type -> Type Source #

Methods

from :: ModelThreeArguments -> Rep ModelThreeArguments x Source #

to :: Rep ModelThreeArguments x -> ModelThreeArguments Source #

Generic ModelTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep ModelTwoArguments :: Type -> Type Source #

Methods

from :: ModelTwoArguments -> Rep ModelTwoArguments x Source #

to :: Rep ModelTwoArguments x -> ModelTwoArguments Source #

Generic Support 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep Support :: Type -> Type Source #

Methods

from :: Support -> Rep Support x Source #

to :: Rep Support x -> Support Source #

Generic CkUserError 
Instance details

Defined in PlutusCore.Evaluation.Machine.Ck

Associated Types

type Rep CkUserError :: Type -> Type Source #

Methods

from :: CkUserError -> Rep CkUserError x Source #

to :: Rep CkUserError x -> CkUserError Source #

Generic StepKind 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep StepKind :: Type -> Type Source #

Methods

from :: StepKind -> Rep StepKind x Source #

to :: Rep StepKind x -> StepKind Source #

Generic TxInInfo 
Instance details

Defined in Plutus.V2.Ledger.Contexts

Associated Types

type Rep TxInInfo :: Type -> Type Source #

Methods

from :: TxInInfo -> Rep TxInInfo x Source #

to :: Rep TxInInfo x -> TxInInfo Source #

Generic StudentT 
Instance details

Defined in Statistics.Distribution.StudentT

Associated Types

type Rep StudentT :: Type -> Type Source #

Methods

from :: StudentT -> Rep StudentT x Source #

to :: Rep StudentT x -> StudentT Source #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type Source #

Methods

from :: ConstructorVariant -> Rep ConstructorVariant x Source #

to :: Rep ConstructorVariant x -> ConstructorVariant Source #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type Source #

Methods

from :: DatatypeVariant -> Rep DatatypeVariant x Source #

to :: Rep DatatypeVariant x -> DatatypeVariant Source #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type Source #

Methods

from :: FieldStrictness -> Rep FieldStrictness x Source #

to :: Rep FieldStrictness x -> FieldStrictness Source #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type Source #

Methods

from :: Strictness -> Rep Strictness x Source #

to :: Rep Strictness x -> Strictness Source #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type Source #

Methods

from :: Unpackedness -> Rep Unpackedness x Source #

to :: Rep Unpackedness x -> Unpackedness Source #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Associated Types

type Rep Specificity :: Type -> Type Source #

Methods

from :: Specificity -> Rep Specificity x Source #

to :: Rep Specificity x -> Specificity Source #

Generic [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type Source #

Methods

from :: [a] -> Rep [a] x Source #

to :: Rep [a] x -> [a] Source #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type Source #

Methods

from :: Maybe a -> Rep (Maybe a) x Source #

to :: Rep (Maybe a) x -> Maybe a Source #

Generic (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type Source #

Methods

from :: Par1 p -> Rep (Par1 p) x Source #

to :: Rep (Par1 p) x -> Par1 p Source #

Generic (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type Source #

Methods

from :: Complex a -> Rep (Complex a) x Source #

to :: Rep (Complex a) x -> Complex a Source #

Generic (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type Source #

Methods

from :: Min a -> Rep (Min a) x Source #

to :: Rep (Min a) x -> Min a Source #

Generic (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type Source #

Methods

from :: Max a -> Rep (Max a) x Source #

to :: Rep (Max a) x -> Max a Source #

Generic (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type Source #

Methods

from :: First a -> Rep (First a) x Source #

to :: Rep (First a) x -> First a Source #

Generic (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type Source #

Methods

from :: Last a -> Rep (Last a) x Source #

to :: Rep (Last a) x -> Last a Source #

Generic (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type Source #

Generic (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type Source #

Methods

from :: Option a -> Rep (Option a) x Source #

to :: Rep (Option a) x -> Option a Source #

Generic (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type Source #

Methods

from :: ZipList a -> Rep (ZipList a) x Source #

to :: Rep (ZipList a) x -> ZipList a Source #

Generic (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type Source #

Methods

from :: Identity a -> Rep (Identity a) x Source #

to :: Rep (Identity a) x -> Identity a Source #

Generic (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type Source #

Methods

from :: First a -> Rep (First a) x Source #

to :: Rep (First a) x -> First a Source #

Generic (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type Source #

Methods

from :: Last a -> Rep (Last a) x Source #

to :: Rep (Last a) x -> Last a Source #

Generic (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type Source #

Methods

from :: Dual a -> Rep (Dual a) x Source #

to :: Rep (Dual a) x -> Dual a Source #

Generic (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type Source #

Methods

from :: Endo a -> Rep (Endo a) x Source #

to :: Rep (Endo a) x -> Endo a Source #

Generic (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type Source #

Methods

from :: Sum a -> Rep (Sum a) x Source #

to :: Rep (Sum a) x -> Sum a Source #

Generic (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type Source #

Methods

from :: Product a -> Rep (Product a) x Source #

to :: Rep (Product a) x -> Product a Source #

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type Source #

Methods

from :: Down a -> Rep (Down a) x Source #

to :: Rep (Down a) x -> Down a Source #

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type Source #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x Source #

to :: Rep (NonEmpty a) x -> NonEmpty a Source #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type Source #

Methods

from :: Doc a -> Rep (Doc a) x Source #

to :: Rep (Doc a) x -> Doc a Source #

Generic (Request o) 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep (Request o) :: Type -> Type Source #

Methods

from :: Request o -> Rep (Request o) x Source #

to :: Rep (Request o) x -> Request o Source #

Generic (Response i) 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep (Response i) :: Type -> Type Source #

Methods

from :: Response i -> Rep (Response i) x Source #

to :: Rep (Response i) x -> Response i Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type Source #

Methods

from :: Doc ann -> Rep (Doc ann) x Source #

to :: Rep (Doc ann) x -> Doc ann Source #

Generic (LogMessage a) 
Instance details

Defined in Control.Monad.Freer.Extras.Log

Associated Types

type Rep (LogMessage a) :: Type -> Type Source #

Methods

from :: LogMessage a -> Rep (LogMessage a) x Source #

to :: Rep (LogMessage a) x -> LogMessage a Source #

Generic (CheckpointStoreItem a) 
Instance details

Defined in Plutus.Contract.Checkpoint

Associated Types

type Rep (CheckpointStoreItem a) :: Type -> Type Source #

Methods

from :: CheckpointStoreItem a -> Rep (CheckpointStoreItem a) x Source #

to :: Rep (CheckpointStoreItem a) x -> CheckpointStoreItem a Source #

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type Source #

Methods

from :: Elem a -> Rep (Elem a) x Source #

to :: Rep (Elem a) x -> Elem a Source #

GenericRec r => Generic (Rec r) 
Instance details

Defined in Data.Row.Records

Associated Types

type Rep (Rec r) :: Type -> Type Source #

Methods

from :: Rec r -> Rep (Rec r) x Source #

to :: Rep (Rec r) x -> Rec r Source #

GenericVar r => Generic (Var r) 
Instance details

Defined in Data.Row.Variants

Associated Types

type Rep (Var r) :: Type -> Type Source #

Methods

from :: Var r -> Rep (Var r) x Source #

to :: Rep (Var r) x -> Var r Source #

Generic (EmulatorTimeEvent e) 
Instance details

Defined in Wallet.Emulator.MultiAgent

Associated Types

type Rep (EmulatorTimeEvent e) :: Type -> Type Source #

Methods

from :: EmulatorTimeEvent e -> Rep (EmulatorTimeEvent e) x Source #

to :: Rep (EmulatorTimeEvent e) x -> EmulatorTimeEvent e Source #

Generic (Action (WithInstances s)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Associated Types

type Rep (Action (WithInstances s)) :: Type -> Type Source #

Methods

from :: Action (WithInstances s) -> Rep (Action (WithInstances s)) x Source #

to :: Rep (Action (WithInstances s)) x -> Action (WithInstances s) Source #

Generic (Action (WrappedState state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

type Rep (Action (WrappedState state)) :: Type -> Type Source #

Methods

from :: Action (WrappedState state) -> Rep (Action (WrappedState state)) x Source #

to :: Rep (Action (WrappedState state)) x -> Action (WrappedState state) Source #

Generic (ModelState state) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Spec

Associated Types

type Rep (ModelState state) :: Type -> Type Source #

Methods

from :: ModelState state -> Rep (ModelState state) x Source #

to :: Rep (ModelState state) x -> ModelState state Source #

Generic (Type l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Type l) :: Type -> Type Source #

Methods

from :: Type l -> Rep (Type l) x Source #

to :: Rep (Type l) x -> Type l Source #

Generic (ModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModuleName l) :: Type -> Type Source #

Methods

from :: ModuleName l -> Rep (ModuleName l) x Source #

to :: Rep (ModuleName l) x -> ModuleName l Source #

Generic (Exp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Exp l) :: Type -> Type Source #

Methods

from :: Exp l -> Rep (Exp l) x Source #

to :: Rep (Exp l) x -> Exp l Source #

Generic (Asst l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Asst l) :: Type -> Type Source #

Methods

from :: Asst l -> Rep (Asst l) x Source #

to :: Rep (Asst l) x -> Asst l Source #

Generic (Name l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Name l) :: Type -> Type Source #

Methods

from :: Name l -> Rep (Name l) x Source #

to :: Rep (Name l) x -> Name l Source #

Generic (ImportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpec l) :: Type -> Type Source #

Methods

from :: ImportSpec l -> Rep (ImportSpec l) x Source #

to :: Rep (ImportSpec l) x -> ImportSpec l Source #

Generic (Activation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Activation l) :: Type -> Type Source #

Methods

from :: Activation l -> Rep (Activation l) x Source #

to :: Rep (Activation l) x -> Activation l Source #

Generic (Alt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Alt l) :: Type -> Type Source #

Methods

from :: Alt l -> Rep (Alt l) x Source #

to :: Rep (Alt l) x -> Alt l Source #

Generic (GuardedRhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (GuardedRhs l) :: Type -> Type Source #

Methods

from :: GuardedRhs l -> Rep (GuardedRhs l) x Source #

to :: Rep (GuardedRhs l) x -> GuardedRhs l Source #

Generic (Stmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Stmt l) :: Type -> Type Source #

Methods

from :: Stmt l -> Rep (Stmt l) x Source #

to :: Rep (Stmt l) x -> Stmt l Source #

Generic (Binds l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Binds l) :: Type -> Type Source #

Methods

from :: Binds l -> Rep (Binds l) x Source #

to :: Rep (Binds l) x -> Binds l Source #

Generic (Pat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Pat l) :: Type -> Type Source #

Methods

from :: Pat l -> Rep (Pat l) x Source #

to :: Rep (Pat l) x -> Pat l Source #

Generic (Annotation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Annotation l) :: Type -> Type Source #

Methods

from :: Annotation l -> Rep (Annotation l) x Source #

to :: Rep (Annotation l) x -> Annotation l Source #

Generic (Assoc l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Assoc l) :: Type -> Type Source #

Methods

from :: Assoc l -> Rep (Assoc l) x Source #

to :: Rep (Assoc l) x -> Assoc l Source #

Generic (BangType l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (BangType l) :: Type -> Type Source #

Methods

from :: BangType l -> Rep (BangType l) x Source #

to :: Rep (BangType l) x -> BangType l Source #

Generic (BooleanFormula l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (BooleanFormula l) :: Type -> Type Source #

Methods

from :: BooleanFormula l -> Rep (BooleanFormula l) x Source #

to :: Rep (BooleanFormula l) x -> BooleanFormula l Source #

Generic (Bracket l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Bracket l) :: Type -> Type Source #

Methods

from :: Bracket l -> Rep (Bracket l) x Source #

to :: Rep (Bracket l) x -> Bracket l Source #

Generic (Decl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Decl l) :: Type -> Type Source #

Methods

from :: Decl l -> Rep (Decl l) x Source #

to :: Rep (Decl l) x -> Decl l Source #

Generic (CName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (CName l) :: Type -> Type Source #

Methods

from :: CName l -> Rep (CName l) x Source #

to :: Rep (CName l) x -> CName l Source #

Generic (CallConv l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (CallConv l) :: Type -> Type Source #

Methods

from :: CallConv l -> Rep (CallConv l) x Source #

to :: Rep (CallConv l) x -> CallConv l Source #

Generic (ClassDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ClassDecl l) :: Type -> Type Source #

Methods

from :: ClassDecl l -> Rep (ClassDecl l) x Source #

to :: Rep (ClassDecl l) x -> ClassDecl l Source #

Generic (ConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ConDecl l) :: Type -> Type Source #

Methods

from :: ConDecl l -> Rep (ConDecl l) x Source #

to :: Rep (ConDecl l) x -> ConDecl l Source #

Generic (FieldDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FieldDecl l) :: Type -> Type Source #

Methods

from :: FieldDecl l -> Rep (FieldDecl l) x Source #

to :: Rep (FieldDecl l) x -> FieldDecl l Source #

Generic (Context l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Context l) :: Type -> Type Source #

Methods

from :: Context l -> Rep (Context l) x Source #

to :: Rep (Context l) x -> Context l Source #

Generic (DataOrNew l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DataOrNew l) :: Type -> Type Source #

Methods

from :: DataOrNew l -> Rep (DataOrNew l) x Source #

to :: Rep (DataOrNew l) x -> DataOrNew l Source #

Generic (DeclHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DeclHead l) :: Type -> Type Source #

Methods

from :: DeclHead l -> Rep (DeclHead l) x Source #

to :: Rep (DeclHead l) x -> DeclHead l Source #

Generic (DerivStrategy l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DerivStrategy l) :: Type -> Type Source #

Methods

from :: DerivStrategy l -> Rep (DerivStrategy l) x Source #

to :: Rep (DerivStrategy l) x -> DerivStrategy l Source #

Generic (Deriving l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Deriving l) :: Type -> Type Source #

Methods

from :: Deriving l -> Rep (Deriving l) x Source #

to :: Rep (Deriving l) x -> Deriving l Source #

Generic (InstRule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstRule l) :: Type -> Type Source #

Methods

from :: InstRule l -> Rep (InstRule l) x Source #

to :: Rep (InstRule l) x -> InstRule l Source #

Generic (FieldUpdate l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FieldUpdate l) :: Type -> Type Source #

Methods

from :: FieldUpdate l -> Rep (FieldUpdate l) x Source #

to :: Rep (FieldUpdate l) x -> FieldUpdate l Source #

Generic (QName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QName l) :: Type -> Type Source #

Methods

from :: QName l -> Rep (QName l) x Source #

to :: Rep (QName l) x -> QName l Source #

Generic (SpecialCon l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (SpecialCon l) :: Type -> Type Source #

Methods

from :: SpecialCon l -> Rep (SpecialCon l) x Source #

to :: Rep (SpecialCon l) x -> SpecialCon l Source #

Generic (FunDep l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FunDep l) :: Type -> Type Source #

Methods

from :: FunDep l -> Rep (FunDep l) x Source #

to :: Rep (FunDep l) x -> FunDep l Source #

Generic (GadtDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (GadtDecl l) :: Type -> Type Source #

Methods

from :: GadtDecl l -> Rep (GadtDecl l) x Source #

to :: Rep (GadtDecl l) x -> GadtDecl l Source #

Generic (TyVarBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (TyVarBind l) :: Type -> Type Source #

Methods

from :: TyVarBind l -> Rep (TyVarBind l) x Source #

to :: Rep (TyVarBind l) x -> TyVarBind l Source #

Generic (Namespace l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Namespace l) :: Type -> Type Source #

Methods

from :: Namespace l -> Rep (Namespace l) x Source #

to :: Rep (Namespace l) x -> Namespace l Source #

Generic (IPBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (IPBind l) :: Type -> Type Source #

Methods

from :: IPBind l -> Rep (IPBind l) x Source #

to :: Rep (IPBind l) x -> IPBind l Source #

Generic (IPName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (IPName l) :: Type -> Type Source #

Methods

from :: IPName l -> Rep (IPName l) x Source #

to :: Rep (IPName l) x -> IPName l Source #

Generic (InjectivityInfo l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InjectivityInfo l) :: Type -> Type Source #

Methods

from :: InjectivityInfo l -> Rep (InjectivityInfo l) x Source #

to :: Rep (InjectivityInfo l) x -> InjectivityInfo l Source #

Generic (InstDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstDecl l) :: Type -> Type Source #

Methods

from :: InstDecl l -> Rep (InstDecl l) x Source #

to :: Rep (InstDecl l) x -> InstDecl l Source #

Generic (InstHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstHead l) :: Type -> Type Source #

Methods

from :: InstHead l -> Rep (InstHead l) x Source #

to :: Rep (InstHead l) x -> InstHead l Source #

Generic (Literal l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Literal l) :: Type -> Type Source #

Methods

from :: Literal l -> Rep (Literal l) x Source #

to :: Rep (Literal l) x -> Literal l Source #

Generic (Match l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Match l) :: Type -> Type Source #

Methods

from :: Match l -> Rep (Match l) x Source #

to :: Rep (Match l) x -> Match l Source #

Generic (MaybePromotedName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (MaybePromotedName l) :: Type -> Type Source #

Methods

from :: MaybePromotedName l -> Rep (MaybePromotedName l) x Source #

to :: Rep (MaybePromotedName l) x -> MaybePromotedName l Source #

Generic (Op l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Op l) :: Type -> Type Source #

Methods

from :: Op l -> Rep (Op l) x Source #

to :: Rep (Op l) x -> Op l Source #

Generic (Overlap l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Overlap l) :: Type -> Type Source #

Methods

from :: Overlap l -> Rep (Overlap l) x Source #

to :: Rep (Overlap l) x -> Overlap l Source #

Generic (PXAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PXAttr l) :: Type -> Type Source #

Methods

from :: PXAttr l -> Rep (PXAttr l) x Source #

to :: Rep (PXAttr l) x -> PXAttr l Source #

Generic (PatField l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PatField l) :: Type -> Type Source #

Methods

from :: PatField l -> Rep (PatField l) x Source #

to :: Rep (PatField l) x -> PatField l Source #

Generic (PatternSynDirection l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PatternSynDirection l) :: Type -> Type Source #

Methods

from :: PatternSynDirection l -> Rep (PatternSynDirection l) x Source #

to :: Rep (PatternSynDirection l) x -> PatternSynDirection l Source #

Generic (Promoted l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Promoted l) :: Type -> Type Source #

Methods

from :: Promoted l -> Rep (Promoted l) x Source #

to :: Rep (Promoted l) x -> Promoted l Source #

Generic (QOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QOp l) :: Type -> Type Source #

Methods

from :: QOp l -> Rep (QOp l) x Source #

to :: Rep (QOp l) x -> QOp l Source #

Generic (QualConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QualConDecl l) :: Type -> Type Source #

Methods

from :: QualConDecl l -> Rep (QualConDecl l) x Source #

to :: Rep (QualConDecl l) x -> QualConDecl l Source #

Generic (QualStmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QualStmt l) :: Type -> Type Source #

Methods

from :: QualStmt l -> Rep (QualStmt l) x Source #

to :: Rep (QualStmt l) x -> QualStmt l Source #

Generic (RPat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RPat l) :: Type -> Type Source #

Methods

from :: RPat l -> Rep (RPat l) x Source #

to :: Rep (RPat l) x -> RPat l Source #

Generic (RPatOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RPatOp l) :: Type -> Type Source #

Methods

from :: RPatOp l -> Rep (RPatOp l) x Source #

to :: Rep (RPatOp l) x -> RPatOp l Source #

Generic (ResultSig l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ResultSig l) :: Type -> Type Source #

Methods

from :: ResultSig l -> Rep (ResultSig l) x Source #

to :: Rep (ResultSig l) x -> ResultSig l Source #

Generic (Rhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Rhs l) :: Type -> Type Source #

Methods

from :: Rhs l -> Rep (Rhs l) x Source #

to :: Rep (Rhs l) x -> Rhs l Source #

Generic (Role l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Role l) :: Type -> Type Source #

Methods

from :: Role l -> Rep (Role l) x Source #

to :: Rep (Role l) x -> Role l Source #

Generic (Rule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Rule l) :: Type -> Type Source #

Methods

from :: Rule l -> Rep (Rule l) x Source #

to :: Rep (Rule l) x -> Rule l Source #

Generic (RuleVar l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RuleVar l) :: Type -> Type Source #

Methods

from :: RuleVar l -> Rep (RuleVar l) x Source #

to :: Rep (RuleVar l) x -> RuleVar l Source #

Generic (Safety l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Safety l) :: Type -> Type Source #

Methods

from :: Safety l -> Rep (Safety l) x Source #

to :: Rep (Safety l) x -> Safety l Source #

Generic (Sign l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Sign l) :: Type -> Type Source #

Methods

from :: Sign l -> Rep (Sign l) x Source #

to :: Rep (Sign l) x -> Sign l Source #

Generic (Splice l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Splice l) :: Type -> Type Source #

Methods

from :: Splice l -> Rep (Splice l) x Source #

to :: Rep (Splice l) x -> Splice l Source #

Generic (TypeEqn l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (TypeEqn l) :: Type -> Type Source #

Methods

from :: TypeEqn l -> Rep (TypeEqn l) x Source #

to :: Rep (TypeEqn l) x -> TypeEqn l Source #

Generic (Unpackedness l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Unpackedness l) :: Type -> Type Source #

Methods

from :: Unpackedness l -> Rep (Unpackedness l) x Source #

to :: Rep (Unpackedness l) x -> Unpackedness l Source #

Generic (XAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (XAttr l) :: Type -> Type Source #

Methods

from :: XAttr l -> Rep (XAttr l) x Source #

to :: Rep (XAttr l) x -> XAttr l Source #

Generic (XName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (XName l) :: Type -> Type Source #

Methods

from :: XName l -> Rep (XName l) x Source #

to :: Rep (XName l) x -> XName l Source #

Generic (ExportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpec l) :: Type -> Type Source #

Methods

from :: ExportSpec l -> Rep (ExportSpec l) x Source #

to :: Rep (ExportSpec l) x -> ExportSpec l Source #

Generic (ModulePragma l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModulePragma l) :: Type -> Type Source #

Methods

from :: ModulePragma l -> Rep (ModulePragma l) x Source #

to :: Rep (ModulePragma l) x -> ModulePragma l Source #

Generic (ModuleHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModuleHead l) :: Type -> Type Source #

Methods

from :: ModuleHead l -> Rep (ModuleHead l) x Source #

to :: Rep (ModuleHead l) x -> ModuleHead l Source #

Generic (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportDecl l) :: Type -> Type Source #

Methods

from :: ImportDecl l -> Rep (ImportDecl l) x Source #

to :: Rep (ImportDecl l) x -> ImportDecl l Source #

Generic (Module l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Module l) :: Type -> Type Source #

Methods

from :: Module l -> Rep (Module l) x Source #

to :: Rep (Module l) x -> Module l Source #

Generic (Finite n) 
Instance details

Defined in Data.Finite.Internal

Associated Types

type Rep (Finite n) :: Type -> Type Source #

Methods

from :: Finite n -> Rep (Finite n) x Source #

to :: Rep (Finite n) x -> Finite n Source #

Generic (QueryResponse a) 
Instance details

Defined in Plutus.ChainIndex.Api

Associated Types

type Rep (QueryResponse a) :: Type -> Type Source #

Methods

from :: QueryResponse a -> Rep (QueryResponse a) x Source #

to :: Rep (QueryResponse a) x -> QueryResponse a Source #

Generic (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep (PageQuery a) :: Type -> Type Source #

Methods

from :: PageQuery a -> Rep (PageQuery a) x Source #

to :: Rep (PageQuery a) x -> PageQuery a Source #

Generic (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep (Page a) :: Type -> Type Source #

Methods

from :: Page a -> Rep (Page a) x Source #

to :: Rep (Page a) x -> Page a Source #

Generic (Versioned script) 
Instance details

Defined in Plutus.Script.Utils.Scripts

Associated Types

type Rep (Versioned script) :: Type -> Type Source #

Methods

from :: Versioned script -> Rep (Versioned script) x Source #

to :: Rep (Versioned script) x -> Versioned script Source #

Generic (Handler a) 
Instance details

Defined in Servant.Server.Internal.Handler

Associated Types

type Rep (Handler a) :: Type -> Type Source #

Methods

from :: Handler a -> Rep (Handler a) x Source #

to :: Rep (Handler a) x -> Handler a Source #

Generic (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (I a) :: Type -> Type Source #

Methods

from :: I a -> Rep (I a) x Source #

to :: Rep (I a) x -> I a Source #

Generic (RollbackState a) 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep (RollbackState a) :: Type -> Type Source #

Methods

from :: RollbackState a -> Rep (RollbackState a) x Source #

to :: Rep (RollbackState a) x -> RollbackState a Source #

Generic (Interval a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (Interval a) :: Type -> Type Source #

Methods

from :: Interval a -> Rep (Interval a) x Source #

to :: Rep (Interval a) x -> Interval a Source #

Generic (LowerBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (LowerBound a) :: Type -> Type Source #

Methods

from :: LowerBound a -> Rep (LowerBound a) x Source #

to :: Rep (LowerBound a) x -> LowerBound a Source #

Generic (Extended a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (Extended a) :: Type -> Type Source #

Methods

from :: Extended a -> Rep (Extended a) x Source #

to :: Rep (Extended a) x -> Extended a Source #

Generic (UpperBound a) 
Instance details

Defined in Plutus.V1.Ledger.Interval

Associated Types

type Rep (UpperBound a) :: Type -> Type Source #

Methods

from :: UpperBound a -> Rep (UpperBound a) x Source #

to :: Rep (UpperBound a) x -> UpperBound a Source #

Generic (OAuth2Flow p) 
Instance details

Defined in Data.OpenApi.Internal

Associated Types

type Rep (OAuth2Flow p) :: Type -> Type Source #

Methods

from :: OAuth2Flow p -> Rep (OAuth2Flow p) x Source #

to :: Rep (OAuth2Flow p) x -> OAuth2Flow p Source #

Generic (ShelleyGenesis era) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesis era) :: Type -> Type Source #

Methods

from :: ShelleyGenesis era -> Rep (ShelleyGenesis era) x Source #

to :: Rep (ShelleyGenesis era) x -> ShelleyGenesis era Source #

Generic (TypedValidator a) 
Instance details

Defined in Plutus.Script.Utils.Typed

Associated Types

type Rep (TypedValidator a) :: Type -> Type Source #

Methods

from :: TypedValidator a -> Rep (TypedValidator a) x Source #

to :: Rep (TypedValidator a) x -> TypedValidator a Source #

Generic (TxOutValue era) 
Instance details

Defined in Cardano.Api.TxBody

Associated Types

type Rep (TxOutValue era) :: Type -> Type Source #

Methods

from :: TxOutValue era -> Rep (TxOutValue era) x Source #

to :: Rep (TxOutValue era) x -> TxOutValue era Source #

Generic (MemoBytes t) 
Instance details

Defined in Data.MemoBytes

Associated Types

type Rep (MemoBytes t) :: Type -> Type Source #

Methods

from :: MemoBytes t -> Rep (MemoBytes t) x Source #

to :: Rep (MemoBytes t) x -> MemoBytes t Source #

Generic (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (SigDSIGN Ed25519DSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x Source #

to :: Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN Source #

Generic (SigDSIGN ByronDSIGN) 
Instance details

Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN

Associated Types

type Rep (SigDSIGN ByronDSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN ByronDSIGN -> Rep (SigDSIGN ByronDSIGN) x Source #

to :: Rep (SigDSIGN ByronDSIGN) x -> SigDSIGN ByronDSIGN Source #

Generic (SigDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

Associated Types

type Rep (SigDSIGN MockDSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN MockDSIGN -> Rep (SigDSIGN MockDSIGN) x Source #

to :: Rep (SigDSIGN MockDSIGN) x -> SigDSIGN MockDSIGN Source #

Generic (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (SigDSIGN EcdsaSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN EcdsaSecp256k1DSIGN -> Rep (SigDSIGN EcdsaSecp256k1DSIGN) x Source #

to :: Rep (SigDSIGN EcdsaSecp256k1DSIGN) x -> SigDSIGN EcdsaSecp256k1DSIGN Source #

Generic (SigDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

Associated Types

type Rep (SigDSIGN Ed448DSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN Ed448DSIGN -> Rep (SigDSIGN Ed448DSIGN) x Source #

to :: Rep (SigDSIGN Ed448DSIGN) x -> SigDSIGN Ed448DSIGN Source #

Generic (SigDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

Associated Types

type Rep (SigDSIGN NeverDSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN NeverDSIGN -> Rep (SigDSIGN NeverDSIGN) x Source #

to :: Rep (SigDSIGN NeverDSIGN) x -> SigDSIGN NeverDSIGN Source #

Generic (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (SigDSIGN SchnorrSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: SigDSIGN SchnorrSecp256k1DSIGN -> Rep (SigDSIGN SchnorrSecp256k1DSIGN) x Source #

to :: Rep (SigDSIGN SchnorrSecp256k1DSIGN) x -> SigDSIGN SchnorrSecp256k1DSIGN Source #

Generic (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (VerKeyDSIGN Ed25519DSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x Source #

to :: Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN Source #

Generic (VerKeyDSIGN ByronDSIGN) 
Instance details

Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN

Associated Types

type Rep (VerKeyDSIGN ByronDSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN ByronDSIGN -> Rep (VerKeyDSIGN ByronDSIGN) x Source #

to :: Rep (VerKeyDSIGN ByronDSIGN) x -> VerKeyDSIGN ByronDSIGN Source #

Generic (VerKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

Associated Types

type Rep (VerKeyDSIGN MockDSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN MockDSIGN -> Rep (VerKeyDSIGN MockDSIGN) x Source #

to :: Rep (VerKeyDSIGN MockDSIGN) x -> VerKeyDSIGN MockDSIGN Source #

Generic (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x Source #

to :: Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x -> VerKeyDSIGN EcdsaSecp256k1DSIGN Source #

Generic (VerKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

Associated Types

type Rep (VerKeyDSIGN Ed448DSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN Ed448DSIGN -> Rep (VerKeyDSIGN Ed448DSIGN) x Source #

to :: Rep (VerKeyDSIGN Ed448DSIGN) x -> VerKeyDSIGN Ed448DSIGN Source #

Generic (VerKeyDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

Associated Types

type Rep (VerKeyDSIGN NeverDSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN NeverDSIGN -> Rep (VerKeyDSIGN NeverDSIGN) x Source #

to :: Rep (VerKeyDSIGN NeverDSIGN) x -> VerKeyDSIGN NeverDSIGN Source #

Generic (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x Source #

to :: Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x -> VerKeyDSIGN SchnorrSecp256k1DSIGN Source #

Generic (TxWitnessRaw era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWitness

Associated Types

type Rep (TxWitnessRaw era) :: Type -> Type Source #

Methods

from :: TxWitnessRaw era -> Rep (TxWitnessRaw era) x Source #

to :: Rep (TxWitnessRaw era) x -> TxWitnessRaw era Source #

Generic (ScriptHash crypto) 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (ScriptHash crypto) :: Type -> Type Source #

Methods

from :: ScriptHash crypto -> Rep (ScriptHash crypto) x Source #

to :: Rep (ScriptHash crypto) x -> ScriptHash crypto Source #

Generic (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Associated Types

type Rep (StrictMaybe a) :: Type -> Type Source #

Methods

from :: StrictMaybe a -> Rep (StrictMaybe a) x Source #

to :: Rep (StrictMaybe a) x -> StrictMaybe a Source #

Generic (BootstrapWitness crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Address.Bootstrap

Associated Types

type Rep (BootstrapWitness crypto) :: Type -> Type Source #

Methods

from :: BootstrapWitness crypto -> Rep (BootstrapWitness crypto) x Source #

to :: Rep (BootstrapWitness crypto) x -> BootstrapWitness crypto Source #

Generic (Script era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep (Script era) :: Type -> Type Source #

Methods

from :: Script era -> Rep (Script era) x Source #

to :: Rep (Script era) x -> Script era Source #

Generic (Data era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Data

Associated Types

type Rep (Data era) :: Type -> Type Source #

Methods

from :: Data era -> Rep (Data era) x Source #

to :: Rep (Data era) x -> Data era Source #

Generic (RedeemersRaw era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWitness

Associated Types

type Rep (RedeemersRaw era) :: Type -> Type Source #

Methods

from :: RedeemersRaw era -> Rep (RedeemersRaw era) x Source #

to :: Rep (RedeemersRaw era) x -> RedeemersRaw era Source #

Generic (TxDatsRaw era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWitness

Associated Types

type Rep (TxDatsRaw era) :: Type -> Type Source #

Methods

from :: TxDatsRaw era -> Rep (TxDatsRaw era) x Source #

to :: Rep (TxDatsRaw era) x -> TxDatsRaw era Source #

Generic (ValidatedTx era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Associated Types

type Rep (ValidatedTx era) :: Type -> Type Source #

Methods

from :: ValidatedTx era -> Rep (ValidatedTx era) x Source #

to :: Rep (ValidatedTx era) x -> ValidatedTx era Source #

Generic (Value crypto) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Associated Types

type Rep (Value crypto) :: Type -> Type Source #

Methods

from :: Value crypto -> Rep (Value crypto) x Source #

to :: Rep (Value crypto) x -> Value crypto Source #

Generic (TxBodyRaw era) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody

Associated Types

type Rep (TxBodyRaw era) :: Type -> Type Source #

Methods

from :: TxBodyRaw era -> Rep (TxBodyRaw era) x Source #

to :: Rep (TxBodyRaw era) x -> TxBodyRaw era Source #

Generic (Addr crypto) 
Instance details

Defined in Cardano.Ledger.Address

Associated Types

type Rep (Addr crypto) :: Type -> Type Source #

Methods

from :: Addr crypto -> Rep (Addr crypto) x Source #

to :: Rep (Addr crypto) x -> Addr crypto Source #

Generic (TxIn crypto) 
Instance details

Defined in Cardano.Ledger.TxIn

Associated Types

type Rep (TxIn crypto) :: Type -> Type Source #

Methods

from :: TxIn crypto -> Rep (TxIn crypto) x Source #

to :: Rep (TxIn crypto) x -> TxIn crypto Source #

Generic (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

type Rep (Fix f) :: Type -> Type Source #

Methods

from :: Fix f -> Rep (Fix f) x Source #

to :: Rep (Fix f) x -> Fix f Source #

Generic (AuxiliaryDataRaw era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Data

Associated Types

type Rep (AuxiliaryDataRaw era) :: Type -> Type Source #

Methods

from :: AuxiliaryDataRaw era -> Rep (AuxiliaryDataRaw era) x Source #

to :: Rep (AuxiliaryDataRaw era) x -> AuxiliaryDataRaw era Source #

Generic (TxId crypto) 
Instance details

Defined in Cardano.Ledger.TxIn

Associated Types

type Rep (TxId crypto) :: Type -> Type Source #

Methods

from :: TxId crypto -> Rep (TxId crypto) x Source #

to :: Rep (TxId crypto) x -> TxId crypto Source #

Generic (Kind ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Kind ann) :: Type -> Type Source #

Methods

from :: Kind ann -> Rep (Kind ann) x Source #

to :: Rep (Kind ann) x -> Kind ann Source #

Generic (SymIndexF f) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep (SymIndexF f) :: Type -> Type Source #

Methods

from :: SymIndexF f -> Rep (SymIndexF f) x Source #

to :: Rep (SymIndexF f) x -> SymIndexF f Source #

Generic (Actions state) 
Instance details

Defined in Test.QuickCheck.StateModel

Associated Types

type Rep (Actions state) :: Type -> Type Source #

Methods

from :: Actions state -> Rep (Actions state) x Source #

to :: Rep (Actions state) x -> Actions state Source #

Generic (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep (WithOrigin t) :: Type -> Type Source #

Methods

from :: WithOrigin t -> Rep (WithOrigin t) x Source #

to :: Rep (WithOrigin t) x -> WithOrigin t Source #

Generic (ShelleyHash crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

type Rep (ShelleyHash crypto) :: Type -> Type Source #

Methods

from :: ShelleyHash crypto -> Rep (ShelleyHash crypto) x Source #

to :: Rep (ShelleyHash crypto) x -> ShelleyHash crypto Source #

Generic (LedgerView crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Associated Types

type Rep (LedgerView crypto) :: Type -> Type Source #

Methods

from :: LedgerView crypto -> Rep (LedgerView crypto) x Source #

to :: Rep (LedgerView crypto) x -> LedgerView crypto Source #

Generic (VerKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep (VerKeyVRF PraosVRF) :: Type -> Type Source #

Methods

from :: VerKeyVRF PraosVRF -> Rep (VerKeyVRF PraosVRF) x Source #

to :: Rep (VerKeyVRF PraosVRF) x -> VerKeyVRF PraosVRF Source #

Generic (VerKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

Associated Types

type Rep (VerKeyVRF MockVRF) :: Type -> Type Source #

Methods

from :: VerKeyVRF MockVRF -> Rep (VerKeyVRF MockVRF) x Source #

to :: Rep (VerKeyVRF MockVRF) x -> VerKeyVRF MockVRF Source #

Generic (VerKeyVRF NeverVRF) 
Instance details

Defined in Cardano.Crypto.VRF.NeverUsed

Associated Types

type Rep (VerKeyVRF NeverVRF) :: Type -> Type Source #

Methods

from :: VerKeyVRF NeverVRF -> Rep (VerKeyVRF NeverVRF) x Source #

to :: Rep (VerKeyVRF NeverVRF) x -> VerKeyVRF NeverVRF Source #

Generic (VerKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Associated Types

type Rep (VerKeyVRF SimpleVRF) :: Type -> Type Source #

Methods

from :: VerKeyVRF SimpleVRF -> Rep (VerKeyVRF SimpleVRF) x Source #

to :: Rep (VerKeyVRF SimpleVRF) x -> VerKeyVRF SimpleVRF Source #

Generic (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (TPraosState c) :: Type -> Type Source #

Methods

from :: TPraosState c -> Rep (TPraosState c) x Source #

to :: Rep (TPraosState c) x -> TPraosState c Source #

Generic (ConsensusConfig (TPraos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (ConsensusConfig (TPraos c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (TPraos c) -> Rep (ConsensusConfig (TPraos c)) x Source #

to :: Rep (ConsensusConfig (TPraos c)) x -> ConsensusConfig (TPraos c) Source #

Generic (ConsensusConfig (Praos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (ConsensusConfig (Praos c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (Praos c) -> Rep (ConsensusConfig (Praos c)) x Source #

to :: Rep (ConsensusConfig (Praos c)) x -> ConsensusConfig (Praos c) Source #

Generic (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (PBft c) -> Rep (ConsensusConfig (PBft c)) x Source #

to :: Rep (ConsensusConfig (PBft c)) x -> ConsensusConfig (PBft c) Source #

Generic (ConsensusConfig (HardForkProtocol xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (ConsensusConfig (HardForkProtocol xs)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (HardForkProtocol xs) -> Rep (ConsensusConfig (HardForkProtocol xs)) x Source #

to :: Rep (ConsensusConfig (HardForkProtocol xs)) x -> ConsensusConfig (HardForkProtocol xs) Source #

Generic (IndividualPoolStake crypto) 
Instance details

Defined in Cardano.Ledger.PoolDistr

Associated Types

type Rep (IndividualPoolStake crypto) :: Type -> Type Source #

Methods

from :: IndividualPoolStake crypto -> Rep (IndividualPoolStake crypto) x Source #

to :: Rep (IndividualPoolStake crypto) x -> IndividualPoolStake crypto Source #

Generic (TopLevelConfig blk) 
Instance details

Defined in Ouroboros.Consensus.Config

Associated Types

type Rep (TopLevelConfig blk) :: Type -> Type Source #

Methods

from :: TopLevelConfig blk -> Rep (TopLevelConfig blk) x Source #

to :: Rep (TopLevelConfig blk) x -> TopLevelConfig blk Source #

Generic (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Associated Types

type Rep (Header ByronBlock) :: Type -> Type Source #

Methods

from :: Header ByronBlock -> Rep (Header ByronBlock) x Source #

to :: Rep (Header ByronBlock) x -> Header ByronBlock Source #

Generic (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: Header (ShelleyBlock proto era) -> Rep (Header (ShelleyBlock proto era)) x Source #

to :: Rep (Header (ShelleyBlock proto era)) x -> Header (ShelleyBlock proto era) Source #

Generic (AHeader a) 
Instance details

Defined in Cardano.Chain.Block.Header

Associated Types

type Rep (AHeader a) :: Type -> Type Source #

Methods

from :: AHeader a -> Rep (AHeader a) x Source #

to :: Rep (AHeader a) x -> AHeader a Source #

Generic (ShelleyPartialLedgerConfig era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type Rep (ShelleyPartialLedgerConfig era) :: Type -> Type Source #

Methods

from :: ShelleyPartialLedgerConfig era -> Rep (ShelleyPartialLedgerConfig era) x Source #

to :: Rep (ShelleyPartialLedgerConfig era) x -> ShelleyPartialLedgerConfig era Source #

Generic (SingleEraInfo blk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Info

Associated Types

type Rep (SingleEraInfo blk) :: Type -> Type Source #

Methods

from :: SingleEraInfo blk -> Rep (SingleEraInfo blk) x Source #

to :: Rep (SingleEraInfo blk) x -> SingleEraInfo blk Source #

Generic (PraosChainSelectView c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Associated Types

type Rep (PraosChainSelectView c) :: Type -> Type Source #

Methods

from :: PraosChainSelectView c -> Rep (PraosChainSelectView c) x Source #

to :: Rep (PraosChainSelectView c) x -> PraosChainSelectView c Source #

Generic (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (Point block) :: Type -> Type Source #

Methods

from :: Point block -> Rep (Point block) x Source #

to :: Rep (Point block) x -> Point block Source #

Generic (PBftCannotForge c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftCannotForge c) :: Type -> Type Source #

Methods

from :: PBftCannotForge c -> Rep (PBftCannotForge c) x Source #

to :: Rep (PBftCannotForge c) x -> PBftCannotForge c Source #

Generic (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerState blk) :: Type -> Type Source #

Methods

from :: ExtLedgerState blk -> Rep (ExtLedgerState blk) x Source #

to :: Rep (ExtLedgerState blk) x -> ExtLedgerState blk Source #

Generic (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (SignKeyDSIGN Ed25519DSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x Source #

to :: Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN Source #

Generic (SignKeyDSIGN ByronDSIGN) 
Instance details

Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN

Associated Types

type Rep (SignKeyDSIGN ByronDSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN ByronDSIGN -> Rep (SignKeyDSIGN ByronDSIGN) x Source #

to :: Rep (SignKeyDSIGN ByronDSIGN) x -> SignKeyDSIGN ByronDSIGN Source #

Generic (SignKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

Associated Types

type Rep (SignKeyDSIGN MockDSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN MockDSIGN -> Rep (SignKeyDSIGN MockDSIGN) x Source #

to :: Rep (SignKeyDSIGN MockDSIGN) x -> SignKeyDSIGN MockDSIGN Source #

Generic (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x Source #

to :: Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x -> SignKeyDSIGN EcdsaSecp256k1DSIGN Source #

Generic (SignKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

Associated Types

type Rep (SignKeyDSIGN Ed448DSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN Ed448DSIGN -> Rep (SignKeyDSIGN Ed448DSIGN) x Source #

to :: Rep (SignKeyDSIGN Ed448DSIGN) x -> SignKeyDSIGN Ed448DSIGN Source #

Generic (SignKeyDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

Associated Types

type Rep (SignKeyDSIGN NeverDSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN NeverDSIGN -> Rep (SignKeyDSIGN NeverDSIGN) x Source #

to :: Rep (SignKeyDSIGN NeverDSIGN) x -> SignKeyDSIGN NeverDSIGN Source #

Generic (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) :: Type -> Type Source #

Methods

from :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x Source #

to :: Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x -> SignKeyDSIGN SchnorrSecp256k1DSIGN Source #

Generic (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderState blk) :: Type -> Type Source #

Methods

from :: HeaderState blk -> Rep (HeaderState blk) x Source #

to :: Rep (HeaderState blk) x -> HeaderState blk Source #

Generic (AnnTip blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (AnnTip blk) :: Type -> Type Source #

Methods

from :: AnnTip blk -> Rep (AnnTip blk) x Source #

to :: Rep (AnnTip blk) x -> AnnTip blk Source #

Generic (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.State

Associated Types

type Rep (PBftState c) :: Type -> Type Source #

Methods

from :: PBftState c -> Rep (PBftState c) x Source #

to :: Rep (PBftState c) x -> PBftState c Source #

Generic (ATxAux a) 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Associated Types

type Rep (ATxAux a) :: Type -> Type Source #

Methods

from :: ATxAux a -> Rep (ATxAux a) x Source #

to :: Rep (ATxAux a) x -> ATxAux a Source #

Generic (ACertificate a) 
Instance details

Defined in Cardano.Chain.Delegation.Certificate

Associated Types

type Rep (ACertificate a) :: Type -> Type Source #

Methods

from :: ACertificate a -> Rep (ACertificate a) x Source #

to :: Rep (ACertificate a) x -> ACertificate a Source #

Generic (AProposal a) 
Instance details

Defined in Cardano.Chain.Update.Proposal

Associated Types

type Rep (AProposal a) :: Type -> Type Source #

Methods

from :: AProposal a -> Rep (AProposal a) x Source #

to :: Rep (AProposal a) x -> AProposal a Source #

Generic (AVote a) 
Instance details

Defined in Cardano.Chain.Update.Vote

Associated Types

type Rep (AVote a) :: Type -> Type Source #

Methods

from :: AVote a -> Rep (AVote a) x Source #

to :: Rep (AVote a) x -> AVote a Source #

Generic (ABlockOrBoundary a) 
Instance details

Defined in Cardano.Chain.Block.Block

Associated Types

type Rep (ABlockOrBoundary a) :: Type -> Type Source #

Methods

from :: ABlockOrBoundary a -> Rep (ABlockOrBoundary a) x Source #

to :: Rep (ABlockOrBoundary a) x -> ABlockOrBoundary a Source #

Generic (ExtLedgerCfg blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerCfg blk) :: Type -> Type Source #

Methods

from :: ExtLedgerCfg blk -> Rep (ExtLedgerCfg blk) x Source #

to :: Rep (ExtLedgerCfg blk) x -> ExtLedgerCfg blk Source #

Generic (PBftLedgerView c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftLedgerView c) :: Type -> Type Source #

Methods

from :: PBftLedgerView c -> Rep (PBftLedgerView c) x Source #

to :: Rep (PBftLedgerView c) x -> PBftLedgerView c Source #

Generic (PBftSigner c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.State

Associated Types

type Rep (PBftSigner c) :: Type -> Type Source #

Methods

from :: PBftSigner c -> Rep (PBftSigner c) x Source #

to :: Rep (PBftSigner c) x -> PBftSigner c Source #

Generic (TipInfoIsEBB blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (TipInfoIsEBB blk) :: Type -> Type Source #

Methods

from :: TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x Source #

to :: Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk Source #

Generic (PBftIsLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftIsLeader c) :: Type -> Type Source #

Methods

from :: PBftIsLeader c -> Rep (PBftIsLeader c) x Source #

to :: Rep (PBftIsLeader c) x -> PBftIsLeader c Source #

Generic (PBftValidationErr c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftValidationErr c) :: Type -> Type Source #

Methods

from :: PBftValidationErr c -> Rep (PBftValidationErr c) x Source #

to :: Rep (PBftValidationErr c) x -> PBftValidationErr c Source #

Generic (ABlockOrBoundaryHdr a) 
Instance details

Defined in Cardano.Chain.Block.Block

Associated Types

type Rep (ABlockOrBoundaryHdr a) :: Type -> Type Source #

Methods

from :: ABlockOrBoundaryHdr a -> Rep (ABlockOrBoundaryHdr a) x Source #

to :: Rep (ABlockOrBoundaryHdr a) x -> ABlockOrBoundaryHdr a Source #

Generic (ABoundaryHeader a) 
Instance details

Defined in Cardano.Chain.Block.Header

Associated Types

type Rep (ABoundaryHeader a) :: Type -> Type Source #

Methods

from :: ABoundaryHeader a -> Rep (ABoundaryHeader a) x Source #

to :: Rep (ABoundaryHeader a) x -> ABoundaryHeader a Source #

Generic (ABoundaryBlock a) 
Instance details

Defined in Cardano.Chain.Block.Block

Associated Types

type Rep (ABoundaryBlock a) :: Type -> Type Source #

Methods

from :: ABoundaryBlock a -> Rep (ABoundaryBlock a) x Source #

to :: Rep (ABoundaryBlock a) x -> ABoundaryBlock a Source #

Generic (ABlock a) 
Instance details

Defined in Cardano.Chain.Block.Block

Associated Types

type Rep (ABlock a) :: Type -> Type Source #

Methods

from :: ABlock a -> Rep (ABlock a) x Source #

to :: Rep (ABlock a) x -> ABlock a Source #

Generic (BHeader crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Associated Types

type Rep (BHeader crypto) :: Type -> Type Source #

Methods

from :: BHeader crypto -> Rep (BHeader crypto) x Source #

to :: Rep (BHeader crypto) x -> BHeader crypto Source #

Generic (PrevHash crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Associated Types

type Rep (PrevHash crypto) :: Type -> Type Source #

Methods

from :: PrevHash crypto -> Rep (PrevHash crypto) x Source #

to :: Rep (PrevHash crypto) x -> PrevHash crypto Source #

Generic (HeaderBody crypto) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Header

Associated Types

type Rep (HeaderBody crypto) :: Type -> Type Source #

Methods

from :: HeaderBody crypto -> Rep (HeaderBody crypto) x Source #

to :: Rep (HeaderBody crypto) x -> HeaderBody crypto Source #

Generic (PraosCanBeLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Associated Types

type Rep (PraosCanBeLeader c) :: Type -> Type Source #

Methods

from :: PraosCanBeLeader c -> Rep (PraosCanBeLeader c) x Source #

to :: Rep (PraosCanBeLeader c) x -> PraosCanBeLeader c Source #

Generic (HeaderRaw crypto) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Header

Associated Types

type Rep (HeaderRaw crypto) :: Type -> Type Source #

Methods

from :: HeaderRaw crypto -> Rep (HeaderRaw crypto) x Source #

to :: Rep (HeaderRaw crypto) x -> HeaderRaw crypto Source #

Generic (VerKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (VerKeyKES (SingleKES d)) :: Type -> Type Source #

Methods

from :: VerKeyKES (SingleKES d) -> Rep (VerKeyKES (SingleKES d)) x Source #

to :: Rep (VerKeyKES (SingleKES d)) x -> VerKeyKES (SingleKES d) Source #

Generic (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (VerKeyKES (SumKES h d)) :: Type -> Type Source #

Methods

from :: VerKeyKES (SumKES h d) -> Rep (VerKeyKES (SumKES h d)) x Source #

to :: Rep (VerKeyKES (SumKES h d)) x -> VerKeyKES (SumKES h d) Source #

Generic (VerKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (VerKeyKES (CompactSingleKES d)) :: Type -> Type Source #

Methods

from :: VerKeyKES (CompactSingleKES d) -> Rep (VerKeyKES (CompactSingleKES d)) x Source #

to :: Rep (VerKeyKES (CompactSingleKES d)) x -> VerKeyKES (CompactSingleKES d) Source #

Generic (VerKeyKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (VerKeyKES (CompactSumKES h d)) :: Type -> Type Source #

Methods

from :: VerKeyKES (CompactSumKES h d) -> Rep (VerKeyKES (CompactSumKES h d)) x Source #

to :: Rep (VerKeyKES (CompactSumKES h d)) x -> VerKeyKES (CompactSumKES h d) Source #

Generic (VerKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (VerKeyKES (MockKES t)) :: Type -> Type Source #

Methods

from :: VerKeyKES (MockKES t) -> Rep (VerKeyKES (MockKES t)) x Source #

to :: Rep (VerKeyKES (MockKES t)) x -> VerKeyKES (MockKES t) Source #

Generic (VerKeyKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (VerKeyKES NeverKES) :: Type -> Type Source #

Methods

from :: VerKeyKES NeverKES -> Rep (VerKeyKES NeverKES) x Source #

to :: Rep (VerKeyKES NeverKES) x -> VerKeyKES NeverKES Source #

Generic (VerKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (VerKeyKES (SimpleKES d t)) :: Type -> Type Source #

Methods

from :: VerKeyKES (SimpleKES d t) -> Rep (VerKeyKES (SimpleKES d t)) x Source #

to :: Rep (VerKeyKES (SimpleKES d t)) x -> VerKeyKES (SimpleKES d t) Source #

Generic (SigKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (SigKES (SingleKES d)) :: Type -> Type Source #

Methods

from :: SigKES (SingleKES d) -> Rep (SigKES (SingleKES d)) x Source #

to :: Rep (SigKES (SingleKES d)) x -> SigKES (SingleKES d) Source #

Generic (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (SigKES (SumKES h d)) :: Type -> Type Source #

Methods

from :: SigKES (SumKES h d) -> Rep (SigKES (SumKES h d)) x Source #

to :: Rep (SigKES (SumKES h d)) x -> SigKES (SumKES h d) Source #

Generic (SigKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (SigKES (CompactSingleKES d)) :: Type -> Type Source #

Methods

from :: SigKES (CompactSingleKES d) -> Rep (SigKES (CompactSingleKES d)) x Source #

to :: Rep (SigKES (CompactSingleKES d)) x -> SigKES (CompactSingleKES d) Source #

Generic (SigKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SigKES (CompactSumKES h d)) :: Type -> Type Source #

Methods

from :: SigKES (CompactSumKES h d) -> Rep (SigKES (CompactSumKES h d)) x Source #

to :: Rep (SigKES (CompactSumKES h d)) x -> SigKES (CompactSumKES h d) Source #

Generic (SigKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SigKES (MockKES t)) :: Type -> Type Source #

Methods

from :: SigKES (MockKES t) -> Rep (SigKES (MockKES t)) x Source #

to :: Rep (SigKES (MockKES t)) x -> SigKES (MockKES t) Source #

Generic (SigKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (SigKES NeverKES) :: Type -> Type Source #

Methods

from :: SigKES NeverKES -> Rep (SigKES NeverKES) x Source #

to :: Rep (SigKES NeverKES) x -> SigKES NeverKES Source #

Generic (SigKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SigKES (SimpleKES d t)) :: Type -> Type Source #

Methods

from :: SigKES (SimpleKES d t) -> Rep (SigKES (SimpleKES d t)) x Source #

to :: Rep (SigKES (SimpleKES d t)) x -> SigKES (SimpleKES d t) Source #

Generic (PraosCannotForge c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosCannotForge c) :: Type -> Type Source #

Methods

from :: PraosCannotForge c -> Rep (PraosCannotForge c) x Source #

to :: Rep (PraosCannotForge c) x -> PraosCannotForge c Source #

Generic (ShelleyLedgerConfig era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyLedgerConfig era) :: Type -> Type Source #

Methods

from :: ShelleyLedgerConfig era -> Rep (ShelleyLedgerConfig era) x Source #

to :: Rep (ShelleyLedgerConfig era) x -> ShelleyLedgerConfig era Source #

Generic (ShelleyGenesisStaking crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesisStaking crypto) :: Type -> Type Source #

Methods

from :: ShelleyGenesisStaking crypto -> Rep (ShelleyGenesisStaking crypto) x Source #

to :: Rep (ShelleyGenesisStaking crypto) x -> ShelleyGenesisStaking crypto Source #

Generic (GenDelegPair crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (GenDelegPair crypto) :: Type -> Type Source #

Methods

from :: GenDelegPair crypto -> Rep (GenDelegPair crypto) x Source #

to :: Rep (GenDelegPair crypto) x -> GenDelegPair crypto Source #

Generic (NewEpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (NewEpochState era) :: Type -> Type Source #

Methods

from :: NewEpochState era -> Rep (NewEpochState era) x Source #

to :: Rep (NewEpochState era) x -> NewEpochState era Source #

Generic (CompactGenesis era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (CompactGenesis era) :: Type -> Type Source #

Methods

from :: CompactGenesis era -> Rep (CompactGenesis era) x Source #

to :: Rep (CompactGenesis era) x -> CompactGenesis era Source #

Generic (PPUPState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (PPUPState era) :: Type -> Type Source #

Methods

from :: PPUPState era -> Rep (PPUPState era) x Source #

to :: Rep (PPUPState era) x -> PPUPState era Source #

Generic (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosState c) :: Type -> Type Source #

Methods

from :: PraosState c -> Rep (PraosState c) x Source #

to :: Rep (PraosState c) x -> PraosState c Source #

Generic (WithTop a) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (WithTop a) :: Type -> Type Source #

Methods

from :: WithTop a -> Rep (WithTop a) x Source #

to :: Rep (WithTop a) x -> WithTop a Source #

Generic (ExUnits' a) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep (ExUnits' a) :: Type -> Type Source #

Methods

from :: ExUnits' a -> Rep (ExUnits' a) x Source #

to :: Rep (ExUnits' a) x -> ExUnits' a Source #

Generic (PoolParams crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (PoolParams crypto) :: Type -> Type Source #

Methods

from :: PoolParams crypto -> Rep (PoolParams crypto) x Source #

to :: Rep (PoolParams crypto) x -> PoolParams crypto Source #

Generic (UTxO era) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

Associated Types

type Rep (UTxO era) :: Type -> Type Source #

Methods

from :: UTxO era -> Rep (UTxO era) x Source #

to :: Rep (UTxO era) x -> UTxO era Source #

Generic (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

type Rep (ProposedPPUpdates era) :: Type -> Type Source #

Methods

from :: ProposedPPUpdates era -> Rep (ProposedPPUpdates era) x Source #

to :: Rep (ProposedPPUpdates era) x -> ProposedPPUpdates era Source #

Generic (EpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (EpochState era) :: Type -> Type Source #

Methods

from :: EpochState era -> Rep (EpochState era) x Source #

to :: Rep (EpochState era) x -> EpochState era Source #

Generic (RewardProvenance crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardProvenance

Associated Types

type Rep (RewardProvenance crypto) :: Type -> Type Source #

Methods

from :: RewardProvenance crypto -> Rep (RewardProvenance crypto) x Source #

to :: Rep (RewardProvenance crypto) x -> RewardProvenance crypto Source #

Generic (ShelleyLedgerError era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyLedgerError era) :: Type -> Type Source #

Methods

from :: ShelleyLedgerError era -> Rep (ShelleyLedgerError era) x Source #

to :: Rep (ShelleyLedgerError era) x -> ShelleyLedgerError era Source #

Generic (BlockTransitionError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Validation

Associated Types

type Rep (BlockTransitionError era) :: Type -> Type Source #

Methods

from :: BlockTransitionError era -> Rep (BlockTransitionError era) x Source #

to :: Rep (BlockTransitionError era) x -> BlockTransitionError era Source #

Generic (HardForkApplyTxErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (HardForkApplyTxErr xs) :: Type -> Type Source #

Methods

from :: HardForkApplyTxErr xs -> Rep (HardForkApplyTxErr xs) x Source #

to :: Rep (HardForkApplyTxErr xs) x -> HardForkApplyTxErr xs Source #

Generic (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkEnvelopeErr xs) :: Type -> Type Source #

Methods

from :: HardForkEnvelopeErr xs -> Rep (HardForkEnvelopeErr xs) x Source #

to :: Rep (HardForkEnvelopeErr xs) x -> HardForkEnvelopeErr xs Source #

Generic (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkLedgerError xs) :: Type -> Type Source #

Methods

from :: HardForkLedgerError xs -> Rep (HardForkLedgerError xs) x Source #

to :: Rep (HardForkLedgerError xs) x -> HardForkLedgerError xs Source #

Generic (HardForkValidationErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

Associated Types

type Rep (HardForkValidationErr xs) :: Type -> Type Source #

Methods

from :: HardForkValidationErr xs -> Rep (HardForkValidationErr xs) x Source #

to :: Rep (HardForkValidationErr xs) x -> HardForkValidationErr xs Source #

Generic (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (HeaderFields b) :: Type -> Type Source #

Methods

from :: HeaderFields b -> Rep (HeaderFields b) x Source #

to :: Rep (HeaderFields b) x -> HeaderFields b Source #

Generic (ChainHash b) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (ChainHash b) :: Type -> Type Source #

Methods

from :: ChainHash b -> Rep (ChainHash b) x Source #

to :: Rep (ChainHash b) x -> ChainHash b Source #

Generic (Handle h) 
Instance details

Defined in Ouroboros.Consensus.Storage.FS.API.Types

Associated Types

type Rep (Handle h) :: Type -> Type Source #

Methods

from :: Handle h -> Rep (Handle h) x Source #

to :: Rep (Handle h) x -> Handle h Source #

Generic (ConnectionId addr) 
Instance details

Defined in Ouroboros.Network.ConnectionId

Associated Types

type Rep (ConnectionId addr) :: Type -> Type Source #

Methods

from :: ConnectionId addr -> Rep (ConnectionId addr) x Source #

to :: Rep (ConnectionId addr) x -> ConnectionId addr Source #

Generic (BHBody crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Associated Types

type Rep (BHBody crypto) :: Type -> Type Source #

Methods

from :: BHBody crypto -> Rep (BHBody crypto) x Source #

to :: Rep (BHBody crypto) x -> BHBody crypto Source #

Generic (TPraosIsLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (TPraosIsLeader c) :: Type -> Type Source #

Methods

from :: TPraosIsLeader c -> Rep (TPraosIsLeader c) x Source #

to :: Rep (TPraosIsLeader c) x -> TPraosIsLeader c Source #

Generic (TPraosToSign c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (TPraosToSign c) :: Type -> Type Source #

Methods

from :: TPraosToSign c -> Rep (TPraosToSign c) x Source #

to :: Rep (TPraosToSign c) x -> TPraosToSign c Source #

Generic (TPraosCannotForge c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (TPraosCannotForge c) :: Type -> Type Source #

Methods

from :: TPraosCannotForge c -> Rep (TPraosCannotForge c) x Source #

to :: Rep (TPraosCannotForge c) x -> TPraosCannotForge c Source #

Generic (DPState crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (DPState crypto) :: Type -> Type Source #

Methods

from :: DPState crypto -> Rep (DPState crypto) x Source #

to :: Rep (DPState crypto) x -> DPState crypto Source #

Generic (FutureGenDeleg crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (FutureGenDeleg crypto) :: Type -> Type Source #

Methods

from :: FutureGenDeleg crypto -> Rep (FutureGenDeleg crypto) x Source #

to :: Rep (FutureGenDeleg crypto) x -> FutureGenDeleg crypto Source #

Generic (DState crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (DState crypto) :: Type -> Type Source #

Methods

from :: DState crypto -> Rep (DState crypto) x Source #

to :: Rep (DState crypto) x -> DState crypto Source #

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type Source #

Methods

from :: FingerTree a -> Rep (FingerTree a) x Source #

to :: Rep (FingerTree a) x -> FingerTree a Source #

Generic (LedgerState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (LedgerState era) :: Type -> Type Source #

Methods

from :: LedgerState era -> Rep (LedgerState era) x Source #

to :: Rep (LedgerState era) x -> LedgerState era Source #

Generic (SnapShots crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.EpochBoundary

Associated Types

type Rep (SnapShots crypto) :: Type -> Type Source #

Methods

from :: SnapShots crypto -> Rep (SnapShots crypto) x Source #

to :: Rep (SnapShots crypto) x -> SnapShots crypto Source #

Generic (SnapShot crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.EpochBoundary

Associated Types

type Rep (SnapShot crypto) :: Type -> Type Source #

Methods

from :: SnapShot crypto -> Rep (SnapShot crypto) x Source #

to :: Rep (SnapShot crypto) x -> SnapShot crypto Source #

Generic (GenDelegs crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (GenDelegs crypto) :: Type -> Type Source #

Methods

from :: GenDelegs crypto -> Rep (GenDelegs crypto) x Source #

to :: Rep (GenDelegs crypto) x -> GenDelegs crypto Source #

Generic (IncrementalStake crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (IncrementalStake crypto) :: Type -> Type Source #

Methods

from :: IncrementalStake crypto -> Rep (IncrementalStake crypto) x Source #

to :: Rep (IncrementalStake crypto) x -> IncrementalStake crypto Source #

Generic (InstantaneousRewards crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (InstantaneousRewards crypto) :: Type -> Type Source #

Methods

from :: InstantaneousRewards crypto -> Rep (InstantaneousRewards crypto) x Source #

to :: Rep (InstantaneousRewards crypto) x -> InstantaneousRewards crypto Source #

Generic (NonMyopic crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.PoolRank

Associated Types

type Rep (NonMyopic crypto) :: Type -> Type Source #

Methods

from :: NonMyopic crypto -> Rep (NonMyopic crypto) x Source #

to :: Rep (NonMyopic crypto) x -> NonMyopic crypto Source #

Generic (PState crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (PState crypto) :: Type -> Type Source #

Methods

from :: PState crypto -> Rep (PState crypto) x Source #

to :: Rep (PState crypto) x -> PState crypto Source #

Generic (PulsingRewUpdate crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardUpdate

Associated Types

type Rep (PulsingRewUpdate crypto) :: Type -> Type Source #

Methods

from :: PulsingRewUpdate crypto -> Rep (PulsingRewUpdate crypto) x Source #

to :: Rep (PulsingRewUpdate crypto) x -> PulsingRewUpdate crypto Source #

Generic (Reward crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Rewards

Associated Types

type Rep (Reward crypto) :: Type -> Type Source #

Methods

from :: Reward crypto -> Rep (Reward crypto) x Source #

to :: Rep (Reward crypto) x -> Reward crypto Source #

Generic (RewardUpdate crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardUpdate

Associated Types

type Rep (RewardUpdate crypto) :: Type -> Type Source #

Methods

from :: RewardUpdate crypto -> Rep (RewardUpdate crypto) x Source #

to :: Rep (RewardUpdate crypto) x -> RewardUpdate crypto Source #

Generic (Stake crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.EpochBoundary

Associated Types

type Rep (Stake crypto) :: Type -> Type Source #

Methods

from :: Stake crypto -> Rep (Stake crypto) x Source #

to :: Rep (Stake crypto) x -> Stake crypto Source #

Generic (UTxOState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (UTxOState era) :: Type -> Type Source #

Methods

from :: UTxOState era -> Rep (UTxOState era) x Source #

to :: Rep (UTxOState era) x -> UTxOState era Source #

Generic (BlocksMade crypto) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep (BlocksMade crypto) :: Type -> Type Source #

Methods

from :: BlocksMade crypto -> Rep (BlocksMade crypto) x Source #

to :: Rep (BlocksMade crypto) x -> BlocksMade crypto Source #

Generic (Update era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

type Rep (Update era) :: Type -> Type Source #

Methods

from :: Update era -> Rep (Update era) x Source #

to :: Rep (Update era) x -> Update era Source #

Generic (AuxiliaryData era) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.AuxiliaryData

Associated Types

type Rep (AuxiliaryData era) :: Type -> Type Source #

Methods

from :: AuxiliaryData era -> Rep (AuxiliaryData era) x Source #

to :: Rep (AuxiliaryData era) x -> AuxiliaryData era Source #

Generic (Timelock crypto) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.Timelocks

Associated Types

type Rep (Timelock crypto) :: Type -> Type Source #

Methods

from :: Timelock crypto -> Rep (Timelock crypto) x Source #

to :: Rep (Timelock crypto) x -> Timelock crypto Source #

Generic (TxBody era) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.TxBody

Associated Types

type Rep (TxBody era) :: Type -> Type Source #

Methods

from :: TxBody era -> Rep (TxBody era) x Source #

to :: Rep (TxBody era) x -> TxBody era Source #

Generic (TimelockRaw crypto) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.Timelocks

Associated Types

type Rep (TimelockRaw crypto) :: Type -> Type Source #

Methods

from :: TimelockRaw crypto -> Rep (TimelockRaw crypto) x Source #

to :: Rep (TimelockRaw crypto) x -> TimelockRaw crypto Source #

Generic (AuxiliaryDataRaw era) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.AuxiliaryData

Associated Types

type Rep (AuxiliaryDataRaw era) :: Type -> Type Source #

Methods

from :: AuxiliaryDataRaw era -> Rep (AuxiliaryDataRaw era) x Source #

to :: Rep (AuxiliaryDataRaw era) x -> AuxiliaryDataRaw era Source #

Generic (TxSeq era) 
Instance details

Defined in Cardano.Ledger.Shelley.BlockChain

Associated Types

type Rep (TxSeq era) :: Type -> Type Source #

Methods

from :: TxSeq era -> Rep (TxSeq era) x Source #

to :: Rep (TxSeq era) x -> TxSeq era Source #

Generic (LedgerPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

Associated Types

type Rep (LedgerPredicateFailure era) :: Type -> Type Source #

Methods

from :: LedgerPredicateFailure era -> Rep (LedgerPredicateFailure era) x Source #

to :: Rep (LedgerPredicateFailure era) x -> LedgerPredicateFailure era Source #

Generic (DelegsPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

Associated Types

type Rep (DelegsPredicateFailure era) :: Type -> Type Source #

Methods

from :: DelegsPredicateFailure era -> Rep (DelegsPredicateFailure era) x Source #

to :: Rep (DelegsPredicateFailure era) x -> DelegsPredicateFailure era Source #

Generic (DelplPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

Associated Types

type Rep (DelplPredicateFailure era) :: Type -> Type Source #

Methods

from :: DelplPredicateFailure era -> Rep (DelplPredicateFailure era) x Source #

to :: Rep (DelplPredicateFailure era) x -> DelplPredicateFailure era Source #

Generic (DCert crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (DCert crypto) :: Type -> Type Source #

Methods

from :: DCert crypto -> Rep (DCert crypto) x Source #

to :: Rep (DCert crypto) x -> DCert crypto Source #

Generic (Wdrl crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (Wdrl crypto) :: Type -> Type Source #

Methods

from :: Wdrl crypto -> Rep (Wdrl crypto) x Source #

to :: Rep (Wdrl crypto) x -> Wdrl crypto Source #

Generic (UtxoPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.Rules.Utxo

Associated Types

type Rep (UtxoPredicateFailure era) :: Type -> Type Source #

Methods

from :: UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x Source #

to :: Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era Source #

Generic (UtxowPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

Associated Types

type Rep (UtxowPredicateFailure era) :: Type -> Type Source #

Methods

from :: UtxowPredicateFailure era -> Rep (UtxowPredicateFailure era) x Source #

to :: Rep (UtxowPredicateFailure era) x -> UtxowPredicateFailure era Source #

Generic (Version ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Version ann) :: Type -> Type Source #

Methods

from :: Version ann -> Rep (Version ann) x Source #

to :: Rep (Version ann) x -> Version ann Source #

Generic (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Normalized a) :: Type -> Type Source #

Methods

from :: Normalized a -> Rep (Normalized a) x Source #

to :: Rep (Normalized a) x -> Normalized a Source #

Generic (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorItem t) :: Type -> Type Source #

Methods

from :: ErrorItem t -> Rep (ErrorItem t) x Source #

to :: Rep (ErrorItem t) x -> ErrorItem t Source #

Generic (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorFancy e) :: Type -> Type Source #

Methods

from :: ErrorFancy e -> Rep (ErrorFancy e) x Source #

to :: Rep (ErrorFancy e) x -> ErrorFancy e Source #

Generic (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (PosState s) :: Type -> Type Source #

Methods

from :: PosState s -> Rep (PosState s) x Source #

to :: Rep (PosState s) x -> PosState s Source #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type Source #

Methods

from :: Tree a -> Rep (Tree a) x Source #

to :: Rep (Tree a) x -> Tree a Source #

Generic (UniqueError ann) 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (UniqueError ann) :: Type -> Type Source #

Methods

from :: UniqueError ann -> Rep (UniqueError ann) x Source #

to :: Rep (UniqueError ann) x -> UniqueError ann Source #

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type Source #

Methods

from :: Digit a -> Rep (Digit a) x Source #

to :: Rep (Digit a) x -> Digit a Source #

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type Source #

Methods

from :: Node a -> Rep (Node a) x Source #

to :: Rep (Node a) x -> Node a Source #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type Source #

Methods

from :: ViewL a -> Rep (ViewL a) x Source #

to :: Rep (ViewL a) x -> ViewL a Source #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type Source #

Methods

from :: ViewR a -> Rep (ViewR a) x Source #

to :: Rep (ViewR a) x -> ViewR a Source #

Generic (RewardProvenancePool crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardProvenance

Associated Types

type Rep (RewardProvenancePool crypto) :: Type -> Type Source #

Methods

from :: RewardProvenancePool crypto -> Rep (RewardProvenancePool crypto) x Source #

to :: Rep (RewardProvenancePool crypto) x -> RewardProvenancePool crypto Source #

Generic (RewardAcnt crypto) 
Instance details

Defined in Cardano.Ledger.Address

Associated Types

type Rep (RewardAcnt crypto) :: Type -> Type Source #

Methods

from :: RewardAcnt crypto -> Rep (RewardAcnt crypto) x Source #

to :: Rep (RewardAcnt crypto) x -> RewardAcnt crypto Source #

Generic (Solo a) 
Instance details

Defined in Data.Tuple.Solo

Associated Types

type Rep (Solo a) :: Type -> Type Source #

Methods

from :: Solo a -> Rep (Solo a) x Source #

to :: Rep (Solo a) x -> Solo a Source #

Generic (UtxoState a) 
Instance details

Defined in Plutus.ChainIndex.UtxoState

Associated Types

type Rep (UtxoState a) :: Type -> Type Source #

Methods

from :: UtxoState a -> Rep (UtxoState a) x Source #

to :: Rep (UtxoState a) x -> UtxoState a Source #

Generic (MeasuredDatabaseState be) 
Instance details

Defined in Database.Beam.Migrate.Actions

Associated Types

type Rep (MeasuredDatabaseState be) :: Type -> Type Source #

Methods

from :: MeasuredDatabaseState be -> Rep (MeasuredDatabaseState be) x Source #

to :: Rep (MeasuredDatabaseState be) x -> MeasuredDatabaseState be Source #

Generic (TableColumnHasConstraint be) 
Instance details

Defined in Database.Beam.Migrate.Checks

Associated Types

type Rep (TableColumnHasConstraint be) :: Type -> Type Source #

Methods

from :: TableColumnHasConstraint be -> Rep (TableColumnHasConstraint be) x Source #

to :: Rep (TableColumnHasConstraint be) x -> TableColumnHasConstraint be Source #

Generic (Signature a) 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Associated Types

type Rep (Signature a) :: Type -> Type Source #

Methods

from :: Signature a -> Rep (Signature a) x Source #

to :: Rep (Signature a) x -> Signature a Source #

Generic (Loc a) 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep (Loc a) :: Type -> Type Source #

Methods

from :: Loc a -> Rep (Loc a) x Source #

to :: Rep (Loc a) x -> Loc a Source #

Generic (EWildcard l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (EWildcard l) :: Type -> Type Source #

Methods

from :: EWildcard l -> Rep (EWildcard l) x Source #

to :: Rep (EWildcard l) x -> EWildcard l Source #

Generic (ExportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpecList l) :: Type -> Type Source #

Methods

from :: ExportSpecList l -> Rep (ExportSpecList l) x Source #

to :: Rep (ExportSpecList l) x -> ExportSpecList l Source #

Generic (ImportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpecList l) :: Type -> Type Source #

Methods

from :: ImportSpecList l -> Rep (ImportSpecList l) x Source #

to :: Rep (ImportSpecList l) x -> ImportSpecList l Source #

Generic (WarningText l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (WarningText l) :: Type -> Type Source #

Methods

from :: WarningText l -> Rep (WarningText l) x Source #

to :: Rep (WarningText l) x -> WarningText l Source #

Generic (Resources a) 
Instance details

Defined in Cardano.BM.Stats.Resources

Associated Types

type Rep (Resources a) :: Type -> Type Source #

Methods

from :: Resources a -> Rep (Resources a) x Source #

to :: Rep (Resources a) x -> Resources a Source #

Generic (AddressRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (AddressRowT f) :: Type -> Type Source #

Methods

from :: AddressRowT f -> Rep (AddressRowT f) x Source #

to :: Rep (AddressRowT f) x -> AddressRowT f Source #

Generic (AssetClassRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (AssetClassRowT f) :: Type -> Type Source #

Methods

from :: AssetClassRowT f -> Rep (AssetClassRowT f) x Source #

to :: Rep (AssetClassRowT f) x -> AssetClassRowT f Source #

Generic (DatumRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (DatumRowT f) :: Type -> Type Source #

Methods

from :: DatumRowT f -> Rep (DatumRowT f) x Source #

to :: Rep (DatumRowT f) x -> DatumRowT f Source #

Generic (Db f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (Db f) :: Type -> Type Source #

Methods

from :: Db f -> Rep (Db f) x Source #

to :: Rep (Db f) x -> Db f Source #

Generic (RedeemerRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (RedeemerRowT f) :: Type -> Type Source #

Methods

from :: RedeemerRowT f -> Rep (RedeemerRowT f) x Source #

to :: Rep (RedeemerRowT f) x -> RedeemerRowT f Source #

Generic (ScriptRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (ScriptRowT f) :: Type -> Type Source #

Methods

from :: ScriptRowT f -> Rep (ScriptRowT f) x Source #

to :: Rep (ScriptRowT f) x -> ScriptRowT f Source #

Generic (TipRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (TipRowT f) :: Type -> Type Source #

Methods

from :: TipRowT f -> Rep (TipRowT f) x Source #

to :: Rep (TipRowT f) x -> TipRowT f Source #

Generic (TxRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (TxRowT f) :: Type -> Type Source #

Methods

from :: TxRowT f -> Rep (TxRowT f) x Source #

to :: Rep (TxRowT f) x -> TxRowT f Source #

Generic (UnmatchedInputRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (UnmatchedInputRowT f) :: Type -> Type Source #

Methods

from :: UnmatchedInputRowT f -> Rep (UnmatchedInputRowT f) x Source #

to :: Rep (UnmatchedInputRowT f) x -> UnmatchedInputRowT f Source #

Generic (UnspentOutputRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (UnspentOutputRowT f) :: Type -> Type Source #

Methods

from :: UnspentOutputRowT f -> Rep (UnspentOutputRowT f) x Source #

to :: Rep (UnspentOutputRowT f) x -> UnspentOutputRowT f Source #

Generic (UtxoRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (UtxoRowT f) :: Type -> Type Source #

Methods

from :: UtxoRowT f -> Rep (UtxoRowT f) x Source #

to :: Rep (UtxoRowT f) x -> UtxoRowT f Source #

Generic (EndpointValue a) 
Instance details

Defined in Wallet.Types

Associated Types

type Rep (EndpointValue a) :: Type -> Type Source #

Methods

from :: EndpointValue a -> Rep (EndpointValue a) x Source #

to :: Rep (EndpointValue a) x -> EndpointValue a Source #

Generic (ScriptLookups a) 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep (ScriptLookups a) :: Type -> Type Source #

Methods

from :: ScriptLookups a -> Rep (ScriptLookups a) x Source #

to :: Rep (ScriptLookups a) x -> ScriptLookups a Source #

Generic (Requests o) 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep (Requests o) :: Type -> Type Source #

Methods

from :: Requests o -> Rep (Requests o) x Source #

to :: Rep (Requests o) x -> Requests o Source #

Generic (Responses i) 
Instance details

Defined in Plutus.Contract.Resumable

Associated Types

type Rep (Responses i) :: Type -> Type Source #

Methods

from :: Responses i -> Rep (Responses i) x Source #

to :: Rep (Responses i) x -> Responses i Source #

Generic (Sized a) 
Instance details

Defined in Cardano.Ledger.Serialization

Associated Types

type Rep (Sized a) :: Type -> Type Source #

Methods

from :: Sized a -> Rep (Sized a) x Source #

to :: Rep (Sized a) x -> Sized a Source #

Generic (TxOutDatum datum) 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (TxOutDatum datum) :: Type -> Type Source #

Methods

from :: TxOutDatum datum -> Rep (TxOutDatum datum) x Source #

to :: Rep (TxOutDatum datum) x -> TxOutDatum datum Source #

Generic (ScriptInputConstraint a) 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (ScriptInputConstraint a) :: Type -> Type Source #

Methods

from :: ScriptInputConstraint a -> Rep (ScriptInputConstraint a) x Source #

to :: Rep (ScriptInputConstraint a) x -> ScriptInputConstraint a Source #

Generic (ScriptOutputConstraint a) 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (ScriptOutputConstraint a) :: Type -> Type Source #

Methods

from :: ScriptOutputConstraint a -> Rep (ScriptOutputConstraint a) x Source #

to :: Rep (ScriptOutputConstraint a) x -> ScriptOutputConstraint a Source #

Generic (ValidityInterval a) 
Instance details

Defined in Ledger.Tx.Constraints.ValidityInterval

Associated Types

type Rep (ValidityInterval a) :: Type -> Type Source #

Methods

from :: ValidityInterval a -> Rep (ValidityInterval a) x Source #

to :: Rep (ValidityInterval a) x -> ValidityInterval a Source #

Generic (BasicAuthCheck usr) 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Associated Types

type Rep (BasicAuthCheck usr) :: Type -> Type Source #

Methods

from :: BasicAuthCheck usr -> Rep (BasicAuthCheck usr) x Source #

to :: Rep (BasicAuthCheck usr) x -> BasicAuthCheck usr Source #

Generic (BasicAuthResult usr) 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Associated Types

type Rep (BasicAuthResult usr) :: Type -> Type Source #

Methods

from :: BasicAuthResult usr -> Rep (BasicAuthResult usr) x Source #

to :: Rep (BasicAuthResult usr) x -> BasicAuthResult usr Source #

Generic (StakeReference crypto) 
Instance details

Defined in Cardano.Ledger.Credential

Associated Types

type Rep (StakeReference crypto) :: Type -> Type Source #

Methods

from :: StakeReference crypto -> Rep (StakeReference crypto) x Source #

to :: Rep (StakeReference crypto) x -> StakeReference crypto Source #

Generic (MachineError fun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep (MachineError fun) :: Type -> Type Source #

Methods

from :: MachineError fun -> Rep (MachineError fun) x Source #

to :: Rep (MachineError fun) x -> MachineError fun Source #

Generic (UtxoPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

Associated Types

type Rep (UtxoPredicateFailure era) :: Type -> Type Source #

Methods

from :: UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x Source #

to :: Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era Source #

Generic (UtxosPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxos

Associated Types

type Rep (UtxosPredicateFailure era) :: Type -> Type Source #

Methods

from :: UtxosPredicateFailure era -> Rep (UtxosPredicateFailure era) x Source #

to :: Rep (UtxosPredicateFailure era) x -> UtxosPredicateFailure era Source #

Generic (TallyingSt fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep (TallyingSt fun) :: Type -> Type Source #

Methods

from :: TallyingSt fun -> Rep (TallyingSt fun) x Source #

to :: Rep (TallyingSt fun) x -> TallyingSt fun Source #

Generic (Metadata era) 
Instance details

Defined in Cardano.Ledger.Shelley.Metadata

Associated Types

type Rep (Metadata era) :: Type -> Type Source #

Methods

from :: Metadata era -> Rep (Metadata era) x Source #

to :: Rep (Metadata era) x -> Metadata era Source #

Generic (MultiSig crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

Associated Types

type Rep (MultiSig crypto) :: Type -> Type Source #

Methods

from :: MultiSig crypto -> Rep (MultiSig crypto) x Source #

to :: Rep (MultiSig crypto) x -> MultiSig crypto Source #

Generic (MultiSigRaw crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

Associated Types

type Rep (MultiSigRaw crypto) :: Type -> Type Source #

Methods

from :: MultiSigRaw crypto -> Rep (MultiSigRaw crypto) x Source #

to :: Rep (MultiSigRaw crypto) x -> MultiSigRaw crypto Source #

Generic (TxBodyRaw era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody

Associated Types

type Rep (TxBodyRaw era) :: Type -> Type Source #

Methods

from :: TxBodyRaw era -> Rep (TxBodyRaw era) x Source #

to :: Rep (TxBodyRaw era) x -> TxBodyRaw era Source #

Generic (TxBodyRaw era) 
Instance details

Defined in Cardano.Ledger.ShelleyMA.TxBody

Associated Types

type Rep (TxBodyRaw era) :: Type -> Type Source #

Methods

from :: TxBodyRaw era -> Rep (TxBodyRaw era) x Source #

to :: Rep (TxBodyRaw era) x -> TxBodyRaw era Source #

Generic (TxBody era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (TxBody era) :: Type -> Type Source #

Methods

from :: TxBody era -> Rep (TxBody era) x Source #

to :: Rep (TxBody era) x -> TxBody era Source #

Generic (GKeys crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (GKeys crypto) :: Type -> Type Source #

Methods

from :: GKeys crypto -> Rep (GKeys crypto) x Source #

to :: Rep (GKeys crypto) x -> GKeys crypto Source #

Generic (SignKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (SignKeyKES (SingleKES d)) :: Type -> Type Source #

Methods

from :: SignKeyKES (SingleKES d) -> Rep (SignKeyKES (SingleKES d)) x Source #

to :: Rep (SignKeyKES (SingleKES d)) x -> SignKeyKES (SingleKES d) Source #

Generic (SignKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (SignKeyKES (SumKES h d)) :: Type -> Type Source #

Methods

from :: SignKeyKES (SumKES h d) -> Rep (SignKeyKES (SumKES h d)) x Source #

to :: Rep (SignKeyKES (SumKES h d)) x -> SignKeyKES (SumKES h d) Source #

Generic (SignKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (SignKeyKES (CompactSingleKES d)) :: Type -> Type Source #

Methods

from :: SignKeyKES (CompactSingleKES d) -> Rep (SignKeyKES (CompactSingleKES d)) x Source #

to :: Rep (SignKeyKES (CompactSingleKES d)) x -> SignKeyKES (CompactSingleKES d) Source #

Generic (SignKeyKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SignKeyKES (CompactSumKES h d)) :: Type -> Type Source #

Methods

from :: SignKeyKES (CompactSumKES h d) -> Rep (SignKeyKES (CompactSumKES h d)) x Source #

to :: Rep (SignKeyKES (CompactSumKES h d)) x -> SignKeyKES (CompactSumKES h d) Source #

Generic (SignKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SignKeyKES (MockKES t)) :: Type -> Type Source #

Methods

from :: SignKeyKES (MockKES t) -> Rep (SignKeyKES (MockKES t)) x Source #

to :: Rep (SignKeyKES (MockKES t)) x -> SignKeyKES (MockKES t) Source #

Generic (SignKeyKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (SignKeyKES NeverKES) :: Type -> Type Source #

Methods

from :: SignKeyKES NeverKES -> Rep (SignKeyKES NeverKES) x Source #

to :: Rep (SignKeyKES NeverKES) x -> SignKeyKES NeverKES Source #

Generic (SignKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SignKeyKES (SimpleKES d t)) :: Type -> Type Source #

Methods

from :: SignKeyKES (SimpleKES d t) -> Rep (SignKeyKES (SimpleKES d t)) x Source #

to :: Rep (SignKeyKES (SimpleKES d t)) x -> SignKeyKES (SimpleKES d t) Source #

Generic (SignKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep (SignKeyVRF PraosVRF) :: Type -> Type Source #

Methods

from :: SignKeyVRF PraosVRF -> Rep (SignKeyVRF PraosVRF) x Source #

to :: Rep (SignKeyVRF PraosVRF) x -> SignKeyVRF PraosVRF Source #

Generic (SignKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

Associated Types

type Rep (SignKeyVRF MockVRF) :: Type -> Type Source #

Methods

from :: SignKeyVRF MockVRF -> Rep (SignKeyVRF MockVRF) x Source #

to :: Rep (SignKeyVRF MockVRF) x -> SignKeyVRF MockVRF Source #

Generic (SignKeyVRF NeverVRF) 
Instance details

Defined in Cardano.Crypto.VRF.NeverUsed

Associated Types

type Rep (SignKeyVRF NeverVRF) :: Type -> Type Source #

Methods

from :: SignKeyVRF NeverVRF -> Rep (SignKeyVRF NeverVRF) x Source #

to :: Rep (SignKeyVRF NeverVRF) x -> SignKeyVRF NeverVRF Source #

Generic (SignKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Associated Types

type Rep (SignKeyVRF SimpleVRF) :: Type -> Type Source #

Methods

from :: SignKeyVRF SimpleVRF -> Rep (SignKeyVRF SimpleVRF) x Source #

to :: Rep (SignKeyVRF SimpleVRF) x -> SignKeyVRF SimpleVRF Source #

Generic (UtxoPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

Associated Types

type Rep (UtxoPredicateFailure era) :: Type -> Type Source #

Methods

from :: UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x Source #

to :: Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era Source #

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep (Maybe a) :: Type -> Type Source #

Methods

from :: Maybe a -> Rep (Maybe a) x Source #

to :: Rep (Maybe a) x -> Maybe a Source #

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type Source #

Methods

from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x Source #

to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann Source #

Generic (WithInstances s) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Internal

Associated Types

type Rep (WithInstances s) :: Type -> Type Source #

Generic (Last' a) 
Instance details

Defined in Distribution.Compat.Semigroup

Associated Types

type Rep (Last' a) :: Type -> Type Source #

Methods

from :: Last' a -> Rep (Last' a) x Source #

to :: Rep (Last' a) x -> Last' a Source #

Generic (Option' a) 
Instance details

Defined in Distribution.Compat.Semigroup

Associated Types

type Rep (Option' a) :: Type -> Type Source #

Methods

from :: Option' a -> Rep (Option' a) x Source #

to :: Rep (Option' a) x -> Option' a Source #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type Source #

Methods

from :: Only a -> Rep (Only a) x Source #

to :: Rep (Only a) x -> Only a Source #

Generic (Graph a) 
Instance details

Defined in Algebra.Graph

Associated Types

type Rep (Graph a) :: Type -> Type Source #

Methods

from :: Graph a -> Rep (Graph a) x Source #

to :: Rep (Graph a) x -> Graph a Source #

Generic (AdjacencyMap a) 
Instance details

Defined in Algebra.Graph.AdjacencyMap

Associated Types

type Rep (AdjacencyMap a) :: Type -> Type Source #

Methods

from :: AdjacencyMap a -> Rep (AdjacencyMap a) x Source #

to :: Rep (AdjacencyMap a) x -> AdjacencyMap a Source #

Generic (Graph a) 
Instance details

Defined in Algebra.Graph.Undirected

Associated Types

type Rep (Graph a) :: Type -> Type Source #

Methods

from :: Graph a -> Rep (Graph a) x Source #

to :: Rep (Graph a) x -> Graph a Source #

Generic (AdjacencyMap a) 
Instance details

Defined in Algebra.Graph.NonEmpty.AdjacencyMap

Associated Types

type Rep (AdjacencyMap a) :: Type -> Type Source #

Methods

from :: AdjacencyMap a -> Rep (AdjacencyMap a) x Source #

to :: Rep (AdjacencyMap a) x -> AdjacencyMap a Source #

Generic (PraosValidationErr c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosValidationErr c) :: Type -> Type Source #

Methods

from :: PraosValidationErr c -> Rep (PraosValidationErr c) x Source #

to :: Rep (PraosValidationErr c) x -> PraosValidationErr c Source #

Generic (ChainTransitionError crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Associated Types

type Rep (ChainTransitionError crypto) :: Type -> Type Source #

Methods

from :: ChainTransitionError crypto -> Rep (ChainTransitionError crypto) x Source #

to :: Rep (ChainTransitionError crypto) x -> ChainTransitionError crypto Source #

Generic (PrtclPredicateFailure crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

Associated Types

type Rep (PrtclPredicateFailure crypto) :: Type -> Type Source #

Methods

from :: PrtclPredicateFailure crypto -> Rep (PrtclPredicateFailure crypto) x Source #

to :: Rep (PrtclPredicateFailure crypto) x -> PrtclPredicateFailure crypto Source #

Generic (TickfPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Tick

Associated Types

type Rep (TickfPredicateFailure era) :: Type -> Type Source #

Methods

from :: TickfPredicateFailure era -> Rep (TickfPredicateFailure era) x Source #

to :: Rep (TickfPredicateFailure era) x -> TickfPredicateFailure era Source #

Generic (TxSeq era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxSeq

Associated Types

type Rep (TxSeq era) :: Type -> Type Source #

Methods

from :: TxSeq era -> Rep (TxSeq era) x Source #

to :: Rep (TxSeq era) x -> TxSeq era Source #

Generic (Tip b) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (Tip b) :: Type -> Type Source #

Methods

from :: Tip b -> Rep (Tip b) x Source #

to :: Rep (Tip b) x -> Tip b Source #

Generic (OCert crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Associated Types

type Rep (OCert crypto) :: Type -> Type Source #

Methods

from :: OCert crypto -> Rep (OCert crypto) x Source #

to :: Rep (OCert crypto) x -> OCert crypto Source #

Generic (HardForkLedgerConfig xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (HardForkLedgerConfig xs) :: Type -> Type Source #

Methods

from :: HardForkLedgerConfig xs -> Rep (HardForkLedgerConfig xs) x Source #

to :: Rep (HardForkLedgerConfig xs) x -> HardForkLedgerConfig xs Source #

Generic (TxBodyRaw era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (TxBodyRaw era) :: Type -> Type Source #

Methods

from :: TxBodyRaw era -> Rep (TxBodyRaw era) x Source #

to :: Rep (TxBodyRaw era) x -> TxBodyRaw era Source #

Generic (CertVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Associated Types

type Rep (CertVRF PraosVRF) :: Type -> Type Source #

Methods

from :: CertVRF PraosVRF -> Rep (CertVRF PraosVRF) x Source #

to :: Rep (CertVRF PraosVRF) x -> CertVRF PraosVRF Source #

Generic (CertVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

Associated Types

type Rep (CertVRF MockVRF) :: Type -> Type Source #

Methods

from :: CertVRF MockVRF -> Rep (CertVRF MockVRF) x Source #

to :: Rep (CertVRF MockVRF) x -> CertVRF MockVRF Source #

Generic (CertVRF NeverVRF) 
Instance details

Defined in Cardano.Crypto.VRF.NeverUsed

Associated Types

type Rep (CertVRF NeverVRF) :: Type -> Type Source #

Methods

from :: CertVRF NeverVRF -> Rep (CertVRF NeverVRF) x Source #

to :: Rep (CertVRF NeverVRF) x -> CertVRF NeverVRF Source #

Generic (CertVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Associated Types

type Rep (CertVRF SimpleVRF) :: Type -> Type Source #

Methods

from :: CertVRF SimpleVRF -> Rep (CertVRF SimpleVRF) x Source #

to :: Rep (CertVRF SimpleVRF) x -> CertVRF SimpleVRF Source #

Generic (AProtocolMagic a) 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Associated Types

type Rep (AProtocolMagic a) :: Type -> Type Source #

Methods

from :: AProtocolMagic a -> Rep (AProtocolMagic a) x Source #

to :: Rep (AProtocolMagic a) x -> AProtocolMagic a Source #

Generic (RedeemSignature a) 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Signature

Associated Types

type Rep (RedeemSignature a) :: Type -> Type Source #

Methods

from :: RedeemSignature a -> Rep (RedeemSignature a) x Source #

to :: Rep (RedeemSignature a) x -> RedeemSignature a Source #

Generic (ScriptPurpose crypto) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Associated Types

type Rep (ScriptPurpose crypto) :: Type -> Type Source #

Methods

from :: ScriptPurpose crypto -> Rep (ScriptPurpose crypto) x Source #

to :: Rep (ScriptPurpose crypto) x -> ScriptPurpose crypto Source #

Generic (TranslationError crypto) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxInfo

Associated Types

type Rep (TranslationError crypto) :: Type -> Type Source #

Methods

from :: TranslationError crypto -> Rep (TranslationError crypto) x Source #

to :: Rep (TranslationError crypto) x -> TranslationError crypto Source #

Generic (CollectError crypto) 
Instance details

Defined in Cardano.Ledger.Alonzo.PlutusScriptApi

Associated Types

type Rep (CollectError crypto) :: Type -> Type Source #

Methods

from :: CollectError crypto -> Rep (CollectError crypto) x Source #

to :: Rep (CollectError crypto) x -> CollectError crypto Source #

Generic (AlonzoBbodyPredFail era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Bbody

Associated Types

type Rep (AlonzoBbodyPredFail era) :: Type -> Type Source #

Methods

from :: AlonzoBbodyPredFail era -> Rep (AlonzoBbodyPredFail era) x Source #

to :: Rep (AlonzoBbodyPredFail era) x -> AlonzoBbodyPredFail era Source #

Generic (BbodyPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

Associated Types

type Rep (BbodyPredicateFailure era) :: Type -> Type Source #

Methods

from :: BbodyPredicateFailure era -> Rep (BbodyPredicateFailure era) x Source #

to :: Rep (BbodyPredicateFailure era) x -> BbodyPredicateFailure era Source #

Generic (UtxowPredicateFail era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxow

Associated Types

type Rep (UtxowPredicateFail era) :: Type -> Type Source #

Methods

from :: UtxowPredicateFail era -> Rep (UtxowPredicateFail era) x Source #

to :: Rep (UtxowPredicateFail era) x -> UtxowPredicateFail era Source #

Generic (PpupPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

Associated Types

type Rep (PpupPredicateFailure era) :: Type -> Type Source #

Methods

from :: PpupPredicateFailure era -> Rep (PpupPredicateFailure era) x Source #

to :: Rep (PpupPredicateFailure era) x -> PpupPredicateFailure era Source #

Generic (WitHashes crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState

Associated Types

type Rep (WitHashes crypto) :: Type -> Type Source #

Methods

from :: WitHashes crypto -> Rep (WitHashes crypto) x Source #

to :: Rep (WitHashes crypto) x -> WitHashes crypto Source #

Generic (ScriptIntegrity era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Associated Types

type Rep (ScriptIntegrity era) :: Type -> Type Source #

Methods

from :: ScriptIntegrity era -> Rep (ScriptIntegrity era) x Source #

to :: Rep (ScriptIntegrity era) x -> ScriptIntegrity era Source #

Generic (TxOutSource crypto) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxInfo

Associated Types

type Rep (TxOutSource crypto) :: Type -> Type Source #

Methods

from :: TxOutSource crypto -> Rep (TxOutSource crypto) x Source #

to :: Rep (TxOutSource crypto) x -> TxOutSource crypto Source #

Generic (ABoundaryBody a) 
Instance details

Defined in Cardano.Chain.Block.Block

Associated Types

type Rep (ABoundaryBody a) :: Type -> Type Source #

Methods

from :: ABoundaryBody a -> Rep (ABoundaryBody a) x Source #

to :: Rep (ABoundaryBody a) x -> ABoundaryBody a Source #

Generic (ABody a) 
Instance details

Defined in Cardano.Chain.Block.Body

Associated Types

type Rep (ABody a) :: Type -> Type Source #

Methods

from :: ABody a -> Rep (ABody a) x Source #

to :: Rep (ABody a) x -> ABody a Source #

Generic (APayload a) 
Instance details

Defined in Cardano.Chain.Delegation.Payload

Associated Types

type Rep (APayload a) :: Type -> Type Source #

Methods

from :: APayload a -> Rep (APayload a) x Source #

to :: Rep (APayload a) x -> APayload a Source #

Generic (ABlockSignature a) 
Instance details

Defined in Cardano.Chain.Block.Header

Associated Types

type Rep (ABlockSignature a) :: Type -> Type Source #

Methods

from :: ABlockSignature a -> Rep (ABlockSignature a) x Source #

to :: Rep (ABlockSignature a) x -> ABlockSignature a Source #

Generic (ATxPayload a) 
Instance details

Defined in Cardano.Chain.UTxO.TxPayload

Associated Types

type Rep (ATxPayload a) :: Type -> Type Source #

Methods

from :: ATxPayload a -> Rep (ATxPayload a) x Source #

to :: Rep (ATxPayload a) x -> ATxPayload a Source #

Generic (APayload a) 
Instance details

Defined in Cardano.Chain.Update.Payload

Associated Types

type Rep (APayload a) :: Type -> Type Source #

Methods

from :: APayload a -> Rep (APayload a) x Source #

to :: Rep (APayload a) x -> APayload a Source #

Generic (Attributes h) 
Instance details

Defined in Cardano.Chain.Common.Attributes

Associated Types

type Rep (Attributes h) :: Type -> Type Source #

Methods

from :: Attributes h -> Rep (Attributes h) x Source #

to :: Rep (Attributes h) x -> Attributes h Source #

Generic (MerkleNode a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

Associated Types

type Rep (MerkleNode a) :: Type -> Type Source #

Methods

from :: MerkleNode a -> Rep (MerkleNode a) x Source #

to :: Rep (MerkleNode a) x -> MerkleNode a Source #

Generic (MerkleRoot a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

Associated Types

type Rep (MerkleRoot a) :: Type -> Type Source #

Methods

from :: MerkleRoot a -> Rep (MerkleRoot a) x Source #

to :: Rep (MerkleRoot a) x -> MerkleRoot a Source #

Generic (MerkleTree a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

Associated Types

type Rep (MerkleTree a) :: Type -> Type Source #

Methods

from :: MerkleTree a -> Rep (MerkleTree a) x Source #

to :: Rep (MerkleTree a) x -> MerkleTree a Source #

Generic (BootstrapAddress crypto) 
Instance details

Defined in Cardano.Ledger.Address

Associated Types

type Rep (BootstrapAddress crypto) :: Type -> Type Source #

Methods

from :: BootstrapAddress crypto -> Rep (BootstrapAddress crypto) x Source #

to :: Rep (BootstrapAddress crypto) x -> BootstrapAddress crypto Source #

Generic (GenesisCredential crypto) 
Instance details

Defined in Cardano.Ledger.Credential

Associated Types

type Rep (GenesisCredential crypto) :: Type -> Type Source #

Methods

from :: GenesisCredential crypto -> Rep (GenesisCredential crypto) x Source #

to :: Rep (GenesisCredential crypto) x -> GenesisCredential crypto Source #

Generic (TickTransitionError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Validation

Associated Types

type Rep (TickTransitionError era) :: Type -> Type Source #

Methods

from :: TickTransitionError era -> Rep (TickTransitionError era) x Source #

to :: Rep (TickTransitionError era) x -> TickTransitionError era Source #

Generic (TxRaw era) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx

Associated Types

type Rep (TxRaw era) :: Type -> Type Source #

Methods

from :: TxRaw era -> Rep (TxRaw era) x Source #

to :: Rep (TxRaw era) x -> TxRaw era Source #

Generic (RewardSnapShot crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardUpdate

Associated Types

type Rep (RewardSnapShot crypto) :: Type -> Type Source #

Methods

from :: RewardSnapShot crypto -> Rep (RewardSnapShot crypto) x Source #

to :: Rep (RewardSnapShot crypto) x -> RewardSnapShot crypto Source #

Generic (RewardAns c) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardUpdate

Associated Types

type Rep (RewardAns c) :: Type -> Type Source #

Methods

from :: RewardAns c -> Rep (RewardAns c) x Source #

to :: Rep (RewardAns c) x -> RewardAns c Source #

Generic (PPUpdateEnv era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

type Rep (PPUpdateEnv era) :: Type -> Type Source #

Methods

from :: PPUpdateEnv era -> Rep (PPUpdateEnv era) x Source #

to :: Rep (PPUpdateEnv era) x -> PPUpdateEnv era Source #

Generic (FreeVars crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.RewardUpdate

Associated Types

type Rep (FreeVars crypto) :: Type -> Type Source #

Methods

from :: FreeVars crypto -> Rep (FreeVars crypto) x Source #

to :: Rep (FreeVars crypto) x -> FreeVars crypto Source #

Generic (PoolRewardInfo crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Rewards

Associated Types

type Rep (PoolRewardInfo crypto) :: Type -> Type Source #

Methods

from :: PoolRewardInfo crypto -> Rep (PoolRewardInfo crypto) x Source #

to :: Rep (PoolRewardInfo crypto) x -> PoolRewardInfo crypto Source #

Generic (LeaderOnlyReward crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.Rewards

Associated Types

type Rep (LeaderOnlyReward crypto) :: Type -> Type Source #

Methods

from :: LeaderOnlyReward crypto -> Rep (LeaderOnlyReward crypto) x Source #

to :: Rep (LeaderOnlyReward crypto) x -> LeaderOnlyReward crypto Source #

Generic (DelegPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Deleg

Associated Types

type Rep (DelegPredicateFailure era) :: Type -> Type Source #

Methods

from :: DelegPredicateFailure era -> Rep (DelegPredicateFailure era) x Source #

to :: Rep (DelegPredicateFailure era) x -> DelegPredicateFailure era Source #

Generic (PoolPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Pool

Associated Types

type Rep (PoolPredicateFailure era) :: Type -> Type Source #

Methods

from :: PoolPredicateFailure era -> Rep (PoolPredicateFailure era) x Source #

to :: Rep (PoolPredicateFailure era) x -> PoolPredicateFailure era Source #

Generic (EpochPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Epoch

Associated Types

type Rep (EpochPredicateFailure era) :: Type -> Type Source #

Methods

from :: EpochPredicateFailure era -> Rep (EpochPredicateFailure era) x Source #

to :: Rep (EpochPredicateFailure era) x -> EpochPredicateFailure era Source #

Generic (PoolreapPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.PoolReap

Associated Types

type Rep (PoolreapPredicateFailure era) :: Type -> Type Source #

Methods

from :: PoolreapPredicateFailure era -> Rep (PoolreapPredicateFailure era) x Source #

to :: Rep (PoolreapPredicateFailure era) x -> PoolreapPredicateFailure era Source #

Generic (SnapPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Snap

Associated Types

type Rep (SnapPredicateFailure era) :: Type -> Type Source #

Methods

from :: SnapPredicateFailure era -> Rep (SnapPredicateFailure era) x Source #

to :: Rep (SnapPredicateFailure era) x -> SnapPredicateFailure era Source #

Generic (UpecPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Upec

Associated Types

type Rep (UpecPredicateFailure era) :: Type -> Type Source #

Methods

from :: UpecPredicateFailure era -> Rep (UpecPredicateFailure era) x Source #

to :: Rep (UpecPredicateFailure era) x -> UpecPredicateFailure era Source #

Generic (LedgersPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

Associated Types

type Rep (LedgersPredicateFailure era) :: Type -> Type Source #

Methods

from :: LedgersPredicateFailure era -> Rep (LedgersPredicateFailure era) x Source #

to :: Rep (LedgersPredicateFailure era) x -> LedgersPredicateFailure era Source #

Generic (MirPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Mir

Associated Types

type Rep (MirPredicateFailure era) :: Type -> Type Source #

Methods

from :: MirPredicateFailure era -> Rep (MirPredicateFailure era) x Source #

to :: Rep (MirPredicateFailure era) x -> MirPredicateFailure era Source #

Generic (NewEpochPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.NewEpoch

Associated Types

type Rep (NewEpochPredicateFailure era) :: Type -> Type Source #

Methods

from :: NewEpochPredicateFailure era -> Rep (NewEpochPredicateFailure era) x Source #

to :: Rep (NewEpochPredicateFailure era) x -> NewEpochPredicateFailure era Source #

Generic (NewppPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Newpp

Associated Types

type Rep (NewppPredicateFailure era) :: Type -> Type Source #

Methods

from :: NewppPredicateFailure era -> Rep (NewppPredicateFailure era) x Source #

to :: Rep (NewppPredicateFailure era) x -> NewppPredicateFailure era Source #

Generic (RupdPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Rupd

Associated Types

type Rep (RupdPredicateFailure era) :: Type -> Type Source #

Methods

from :: RupdPredicateFailure era -> Rep (RupdPredicateFailure era) x Source #

to :: Rep (RupdPredicateFailure era) x -> RupdPredicateFailure era Source #

Generic (TickEvent era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Tick

Associated Types

type Rep (TickEvent era) :: Type -> Type Source #

Methods

from :: TickEvent era -> Rep (TickEvent era) x Source #

to :: Rep (TickEvent era) x -> TickEvent era Source #

Generic (TickPredicateFailure era) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Tick

Associated Types

type Rep (TickPredicateFailure era) :: Type -> Type Source #

Methods

from :: TickPredicateFailure era -> Rep (TickPredicateFailure era) x Source #

to :: Rep (TickPredicateFailure era) x -> TickPredicateFailure era Source #

Generic (DelegCert crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (DelegCert crypto) :: Type -> Type Source #

Methods

from :: DelegCert crypto -> Rep (DelegCert crypto) x Source #

to :: Rep (DelegCert crypto) x -> DelegCert crypto Source #

Generic (Delegation crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (Delegation crypto) :: Type -> Type Source #

Methods

from :: Delegation crypto -> Rep (Delegation crypto) x Source #

to :: Rep (Delegation crypto) x -> Delegation crypto Source #

Generic (GenesisDelegCert crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (GenesisDelegCert crypto) :: Type -> Type Source #

Methods

from :: GenesisDelegCert crypto -> Rep (GenesisDelegCert crypto) x Source #

to :: Rep (GenesisDelegCert crypto) x -> GenesisDelegCert crypto Source #

Generic (MIRCert crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (MIRCert crypto) :: Type -> Type Source #

Methods

from :: MIRCert crypto -> Rep (MIRCert crypto) x Source #

to :: Rep (MIRCert crypto) x -> MIRCert crypto Source #

Generic (MIRTarget crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (MIRTarget crypto) :: Type -> Type Source #

Methods

from :: MIRTarget crypto -> Rep (MIRTarget crypto) x Source #

to :: Rep (MIRTarget crypto) x -> MIRTarget crypto Source #

Generic (PoolCert crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (PoolCert crypto) :: Type -> Type Source #

Methods

from :: PoolCert crypto -> Rep (PoolCert crypto) x Source #

to :: Rep (PoolCert crypto) x -> PoolCert crypto Source #

Generic (StakeCreds crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (StakeCreds crypto) :: Type -> Type Source #

Methods

from :: StakeCreds crypto -> Rep (StakeCreds crypto) x Source #

to :: Rep (StakeCreds crypto) x -> StakeCreds crypto Source #

Generic (ChainDepState crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Associated Types

type Rep (ChainDepState crypto) :: Type -> Type Source #

Methods

from :: ChainDepState crypto -> Rep (ChainDepState crypto) x Source #

to :: Rep (ChainDepState crypto) x -> ChainDepState crypto Source #

Generic (PrtclState crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

Associated Types

type Rep (PrtclState crypto) :: Type -> Type Source #

Methods

from :: PrtclState crypto -> Rep (PrtclState crypto) x Source #

to :: Rep (PrtclState crypto) x -> PrtclState crypto Source #

Generic (HashHeader crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Associated Types

type Rep (HashHeader crypto) :: Type -> Type Source #

Methods

from :: HashHeader crypto -> Rep (HashHeader crypto) x Source #

to :: Rep (HashHeader crypto) x -> HashHeader crypto Source #

Generic (LastAppliedBlock crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Associated Types

type Rep (LastAppliedBlock crypto) :: Type -> Type Source #

Methods

from :: LastAppliedBlock crypto -> Rep (LastAppliedBlock crypto) x Source #

to :: Rep (LastAppliedBlock crypto) x -> LastAppliedBlock crypto Source #

Generic (OcertPredicateFailure crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.OCert

Associated Types

type Rep (OcertPredicateFailure crypto) :: Type -> Type Source #

Methods

from :: OcertPredicateFailure crypto -> Rep (OcertPredicateFailure crypto) x Source #

to :: Rep (OcertPredicateFailure crypto) x -> OcertPredicateFailure crypto Source #

Generic (OBftSlot crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Overlay

Associated Types

type Rep (OBftSlot crypto) :: Type -> Type Source #

Methods

from :: OBftSlot crypto -> Rep (OBftSlot crypto) x Source #

to :: Rep (OBftSlot crypto) x -> OBftSlot crypto Source #

Generic (OverlayEnv crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Overlay

Associated Types

type Rep (OverlayEnv crypto) :: Type -> Type Source #

Methods

from :: OverlayEnv crypto -> Rep (OverlayEnv crypto) x Source #

to :: Rep (OverlayEnv crypto) x -> OverlayEnv crypto Source #

Generic (OverlayPredicateFailure crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Overlay

Associated Types

type Rep (OverlayPredicateFailure crypto) :: Type -> Type Source #

Methods

from :: OverlayPredicateFailure crypto -> Rep (OverlayPredicateFailure crypto) x Source #

to :: Rep (OverlayPredicateFailure crypto) x -> OverlayPredicateFailure crypto Source #

Generic (PrtclEnv crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

Associated Types

type Rep (PrtclEnv crypto) :: Type -> Type Source #

Methods

from :: PrtclEnv crypto -> Rep (PrtclEnv crypto) x Source #

to :: Rep (PrtclEnv crypto) x -> PrtclEnv crypto Source #

Generic (PrtlSeqFailure crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

Associated Types

type Rep (PrtlSeqFailure crypto) :: Type -> Type Source #

Methods

from :: PrtlSeqFailure crypto -> Rep (PrtlSeqFailure crypto) x Source #

to :: Rep (PrtlSeqFailure crypto) x -> PrtlSeqFailure crypto Source #

Generic (UpdnPredicateFailure crypto) 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Updn

Associated Types

type Rep (UpdnPredicateFailure crypto) :: Type -> Type Source #

Methods

from :: UpdnPredicateFailure crypto -> Rep (UpdnPredicateFailure crypto) x Source #

to :: Rep (UpdnPredicateFailure crypto) x -> UpdnPredicateFailure crypto Source #

Generic (SCC vertex) 
Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex) :: Type -> Type Source #

Methods

from :: SCC vertex -> Rep (SCC vertex) x Source #

to :: Rep (SCC vertex) x -> SCC vertex Source #

Generic (Digit a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (Digit a) :: Type -> Type Source #

Methods

from :: Digit a -> Rep (Digit a) x Source #

to :: Rep (Digit a) x -> Digit a Source #

Generic (PostAligned a) 
Instance details

Defined in Flat.Filler

Associated Types

type Rep (PostAligned a) :: Type -> Type Source #

Methods

from :: PostAligned a -> Rep (PostAligned a) x Source #

to :: Rep (PostAligned a) x -> PostAligned a Source #

Generic (PreAligned a) 
Instance details

Defined in Flat.Filler

Associated Types

type Rep (PreAligned a) :: Type -> Type Source #

Methods

from :: PreAligned a -> Rep (PreAligned a) x Source #

to :: Rep (PreAligned a) x -> PreAligned a Source #

Generic (GenClosure b) 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep (GenClosure b) :: Type -> Type Source #

Methods

from :: GenClosure b -> Rep (GenClosure b) x Source #

to :: Rep (GenClosure b) x -> GenClosure b Source #

Generic (AddrRange a) 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep (AddrRange a) :: Type -> Type Source #

Methods

from :: AddrRange a -> Rep (AddrRange a) x Source #

to :: Rep (AddrRange a) x -> AddrRange a Source #

Generic (Root a) 
Instance details

Defined in Numeric.RootFinding

Associated Types

type Rep (Root a) :: Type -> Type Source #

Methods

from :: Root a -> Rep (Root a) x Source #

to :: Rep (Root a) x -> Root a Source #

Generic (RealPoint blk) 
Instance details

Defined in Ouroboros.Consensus.Block.RealPoint

Associated Types

type Rep (RealPoint blk) :: Type -> Type Source #

Methods

from :: RealPoint blk -> Rep (RealPoint blk) x Source #

to :: Rep (RealPoint blk) x -> RealPoint blk Source #

Generic (HeaderStateHistory blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderStateHistory

Associated Types

type Rep (HeaderStateHistory blk) :: Type -> Type Source #

Methods

from :: HeaderStateHistory blk -> Rep (HeaderStateHistory blk) x Source #

to :: Rep (HeaderStateHistory blk) x -> HeaderStateHistory blk Source #

Generic (HeaderError blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderError blk) :: Type -> Type Source #

Methods

from :: HeaderError blk -> Rep (HeaderError blk) x Source #

to :: Rep (HeaderError blk) x -> HeaderError blk Source #

Generic (HeaderEnvelopeError blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderEnvelopeError blk) :: Type -> Type Source #

Methods

from :: HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x Source #

to :: Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk Source #

Generic (ExtValidationError blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtValidationError blk) :: Type -> Type Source #

Methods

from :: ExtValidationError blk -> Rep (ExtValidationError blk) x Source #

to :: Rep (ExtValidationError blk) x -> ExtValidationError blk Source #

Generic (InternalState blk) 
Instance details

Defined in Ouroboros.Consensus.Mempool.Impl.Types

Associated Types

type Rep (InternalState blk) :: Type -> Type Source #

Methods

from :: InternalState blk -> Rep (InternalState blk) x Source #

to :: Rep (InternalState blk) x -> InternalState blk Source #

Generic (TxTicket tx) 
Instance details

Defined in Ouroboros.Consensus.Mempool.TxSeq

Associated Types

type Rep (TxTicket tx) :: Type -> Type Source #

Methods

from :: TxTicket tx -> Rep (TxTicket tx) x Source #

to :: Rep (TxTicket tx) x -> TxTicket tx Source #

Generic (InvalidBlockReason blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

Associated Types

type Rep (InvalidBlockReason blk) :: Type -> Type Source #

Methods

from :: InvalidBlockReason blk -> Rep (InvalidBlockReason blk) x Source #

to :: Rep (InvalidBlockReason blk) x -> InvalidBlockReason blk Source #

Generic (KnownIntersectionState blk) 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

Associated Types

type Rep (KnownIntersectionState blk) :: Type -> Type Source #

Methods

from :: KnownIntersectionState blk -> Rep (KnownIntersectionState blk) x Source #

to :: Rep (KnownIntersectionState blk) x -> KnownIntersectionState blk Source #

Generic (UnknownIntersectionState blk) 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

Associated Types

type Rep (UnknownIntersectionState blk) :: Type -> Type Source #

Methods

from :: UnknownIntersectionState blk -> Rep (UnknownIntersectionState blk) x Source #

to :: Rep (UnknownIntersectionState blk) x -> UnknownIntersectionState blk Source #

Generic (Anchor block) 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Associated Types

type Rep (Anchor block) :: Type -> Type Source #

Methods

from :: Anchor block -> Rep (Anchor block) x Source #

to :: Rep (Anchor block) x -> Anchor block Source #

Generic (WithFingerprint a) 
Instance details

Defined in Ouroboros.Consensus.Util.STM

Associated Types

type Rep (WithFingerprint a) :: Type -> Type Source #

Methods

from :: WithFingerprint a -> Rep (WithFingerprint a) x Source #

to :: Rep (WithFingerprint a) x -> WithFingerprint a Source #

Generic (LedgerDB l) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.InMemory

Associated Types

type Rep (LedgerDB l) :: Type -> Type Source #

Methods

from :: LedgerDB l -> Rep (LedgerDB l) x Source #

to :: Rep (LedgerDB l) x -> LedgerDB l Source #

Generic (PBftCanBeLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftCanBeLeader c) :: Type -> Type Source #

Methods

from :: PBftCanBeLeader c -> Rep (PBftCanBeLeader c) x Source #

to :: Rep (PBftCanBeLeader c) x -> PBftCanBeLeader c Source #

Generic (StreamFrom blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

Associated Types

type Rep (StreamFrom blk) :: Type -> Type Source #

Methods

from :: StreamFrom blk -> Rep (StreamFrom blk) x Source #

to :: Rep (StreamFrom blk) x -> StreamFrom blk Source #

Generic (StreamTo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

Associated Types

type Rep (StreamTo blk) :: Type -> Type Source #

Methods

from :: StreamTo blk -> Rep (StreamTo blk) x Source #

to :: Rep (StreamTo blk) x -> StreamTo blk Source #

Generic (ResourceRegistry m) 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Associated Types

type Rep (ResourceRegistry m) :: Type -> Type Source #

Methods

from :: ResourceRegistry m -> Rep (ResourceRegistry m) x Source #

to :: Rep (ResourceRegistry m) x -> ResourceRegistry m Source #

Generic (Checkpoint l) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.InMemory

Associated Types

type Rep (Checkpoint l) :: Type -> Type Source #

Methods

from :: Checkpoint l -> Rep (Checkpoint l) x Source #

to :: Rep (Checkpoint l) x -> Checkpoint l Source #

Generic (TraceEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceEvent blk) :: Type -> Type Source #

Methods

from :: TraceEvent blk -> Rep (TraceEvent blk) x Source #

to :: Rep (TraceEvent blk) x -> TraceEvent blk Source #

Generic (InvalidBlockInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (InvalidBlockInfo blk) :: Type -> Type Source #

Methods

from :: InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x Source #

to :: Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk Source #

Generic (TraceAddBlockEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceAddBlockEvent blk) :: Type -> Type Source #

Methods

from :: TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x Source #

to :: Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk Source #

Generic (TraceGCEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceGCEvent blk) :: Type -> Type Source #

Methods

from :: TraceGCEvent blk -> Rep (TraceGCEvent blk) x Source #

to :: Rep (TraceGCEvent blk) x -> TraceGCEvent blk Source #

Generic (InImmutableDBEnd blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Iterator

Associated Types

type Rep (InImmutableDBEnd blk) :: Type -> Type Source #

Methods

from :: InImmutableDBEnd blk -> Rep (InImmutableDBEnd blk) x Source #

to :: Rep (InImmutableDBEnd blk) x -> InImmutableDBEnd blk Source #

Generic (TraceIteratorEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceIteratorEvent blk) :: Type -> Type Source #

Methods

from :: TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x Source #

to :: Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk Source #

Generic (TraceEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.OnDisk

Associated Types

type Rep (TraceEvent blk) :: Type -> Type Source #

Methods

from :: TraceEvent blk -> Rep (TraceEvent blk) x Source #

to :: Rep (TraceEvent blk) x -> TraceEvent blk Source #

Generic (TraceReplayEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.OnDisk

Associated Types

type Rep (TraceReplayEvent blk) :: Type -> Type Source #

Methods

from :: TraceReplayEvent blk -> Rep (TraceReplayEvent blk) x Source #

to :: Rep (TraceReplayEvent blk) x -> TraceReplayEvent blk Source #

Generic (UpdateLedgerDbTraceEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.Types

Associated Types

type Rep (UpdateLedgerDbTraceEvent blk) :: Type -> Type Source #

Methods

from :: UpdateLedgerDbTraceEvent blk -> Rep (UpdateLedgerDbTraceEvent blk) x Source #

to :: Rep (UpdateLedgerDbTraceEvent blk) x -> UpdateLedgerDbTraceEvent blk Source #

Generic (FollowerRollState blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (FollowerRollState blk) :: Type -> Type Source #

Methods

from :: FollowerRollState blk -> Rep (FollowerRollState blk) x Source #

to :: Rep (FollowerRollState blk) x -> FollowerRollState blk Source #

Generic (NewTipInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (NewTipInfo blk) :: Type -> Type Source #

Methods

from :: NewTipInfo blk -> Rep (NewTipInfo blk) x Source #

to :: Rep (NewTipInfo blk) x -> NewTipInfo blk Source #

Generic (TraceCopyToImmutableDBEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceCopyToImmutableDBEvent blk) :: Type -> Type Source #

Methods

from :: TraceCopyToImmutableDBEvent blk -> Rep (TraceCopyToImmutableDBEvent blk) x Source #

to :: Rep (TraceCopyToImmutableDBEvent blk) x -> TraceCopyToImmutableDBEvent blk Source #

Generic (TraceFollowerEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceFollowerEvent blk) :: Type -> Type Source #

Methods

from :: TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x Source #

to :: Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk Source #

Generic (TraceInitChainSelEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceInitChainSelEvent blk) :: Type -> Type Source #

Methods

from :: TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x Source #

to :: Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk Source #

Generic (TraceOpenEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceOpenEvent blk) :: Type -> Type Source #

Methods

from :: TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x Source #

to :: Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk Source #

Generic (TraceValidationEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (TraceValidationEvent blk) :: Type -> Type Source #

Methods

from :: TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x Source #

to :: Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk Source #

Generic (TentativeState blk) 
Instance details

Defined in Ouroboros.Consensus.Util.TentativeState

Associated Types

type Rep (TentativeState blk) :: Type -> Type Source #

Methods

from :: TentativeState blk -> Rep (TentativeState blk) x Source #

to :: Rep (TentativeState blk) x -> TentativeState blk Source #

Generic (TraceEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep (TraceEvent blk) :: Type -> Type Source #

Methods

from :: TraceEvent blk -> Rep (TraceEvent blk) x Source #

to :: Rep (TraceEvent blk) x -> TraceEvent blk Source #

Generic (TraceEvent blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep (TraceEvent blk) :: Type -> Type Source #

Methods

from :: TraceEvent blk -> Rep (TraceEvent blk) x Source #

to :: Rep (TraceEvent blk) x -> TraceEvent blk Source #

Generic (ImmutableDBError blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (ImmutableDBError blk) :: Type -> Type Source #

Methods

from :: ImmutableDBError blk -> Rep (ImmutableDBError blk) x Source #

to :: Rep (ImmutableDBError blk) x -> ImmutableDBError blk Source #

Generic (IteratorResult b) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (IteratorResult b) :: Type -> Type Source #

Methods

from :: IteratorResult b -> Rep (IteratorResult b) x Source #

to :: Rep (IteratorResult b) x -> IteratorResult b Source #

Generic (MissingBlock blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (MissingBlock blk) :: Type -> Type Source #

Methods

from :: MissingBlock blk -> Rep (MissingBlock blk) x Source #

to :: Rep (MissingBlock blk) x -> MissingBlock blk Source #

Generic (Tip blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (Tip blk) :: Type -> Type Source #

Methods

from :: Tip blk -> Rep (Tip blk) x Source #

to :: Rep (Tip blk) x -> Tip blk Source #

Generic (Cached blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache

Associated Types

type Rep (Cached blk) :: Type -> Type Source #

Methods

from :: Cached blk -> Rep (Cached blk) x Source #

to :: Rep (Cached blk) x -> Cached blk Source #

Generic (CurrentChunkInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache

Associated Types

type Rep (CurrentChunkInfo blk) :: Type -> Type Source #

Methods

from :: CurrentChunkInfo blk -> Rep (CurrentChunkInfo blk) x Source #

to :: Rep (CurrentChunkInfo blk) x -> CurrentChunkInfo blk Source #

Generic (PastChunkInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Cache

Associated Types

type Rep (PastChunkInfo blk) :: Type -> Type Source #

Methods

from :: PastChunkInfo blk -> Rep (PastChunkInfo blk) x Source #

to :: Rep (PastChunkInfo blk) x -> PastChunkInfo blk Source #

Generic (Entry blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

Associated Types

type Rep (Entry blk) :: Type -> Type Source #

Methods

from :: Entry blk -> Rep (Entry blk) x Source #

to :: Rep (Entry blk) x -> Entry blk Source #

Generic (WithBlockSize a) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep (WithBlockSize a) :: Type -> Type Source #

Methods

from :: WithBlockSize a -> Rep (WithBlockSize a) x Source #

to :: Rep (WithBlockSize a) x -> WithBlockSize a Source #

Generic (ResourceKey m) 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Associated Types

type Rep (ResourceKey m) :: Type -> Type Source #

Methods

from :: ResourceKey m -> Rep (ResourceKey m) x Source #

to :: Rep (ResourceKey m) x -> ResourceKey m Source #

Generic (LedgerDbCfg l) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.InMemory

Associated Types

type Rep (LedgerDbCfg l) :: Type -> Type Source #

Methods

from :: LedgerDbCfg l -> Rep (LedgerDbCfg l) x Source #

to :: Rep (LedgerDbCfg l) x -> LedgerDbCfg l Source #

Generic (InitFailure blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.OnDisk

Associated Types

type Rep (InitFailure blk) :: Type -> Type Source #

Methods

from :: InitFailure blk -> Rep (InitFailure blk) x Source #

to :: Rep (InitFailure blk) x -> InitFailure blk Source #

Generic (InitLog blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.OnDisk

Associated Types

type Rep (InitLog blk) :: Type -> Type Source #

Methods

from :: InitLog blk -> Rep (InitLog blk) x Source #

to :: Rep (InitLog blk) x -> InitLog blk Source #

Generic (BlockInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.API

Associated Types

type Rep (BlockInfo blk) :: Type -> Type Source #

Methods

from :: BlockInfo blk -> Rep (BlockInfo blk) x Source #

to :: Rep (BlockInfo blk) x -> BlockInfo blk Source #

Generic (FileInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.FileInfo

Associated Types

type Rep (FileInfo blk) :: Type -> Type Source #

Methods

from :: FileInfo blk -> Rep (FileInfo blk) x Source #

to :: Rep (FileInfo blk) x -> FileInfo blk Source #

Generic (Index blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Index

Associated Types

type Rep (Index blk) :: Type -> Type Source #

Methods

from :: Index blk -> Rep (Index blk) x Source #

to :: Rep (Index blk) x -> Index blk Source #

Generic (InternalBlockInfo blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep (InternalBlockInfo blk) :: Type -> Type Source #

Methods

from :: InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x Source #

to :: Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk Source #

Generic (RAWState st) 
Instance details

Defined in Ouroboros.Consensus.Util.MonadSTM.RAWLock

Associated Types

type Rep (RAWState st) :: Type -> Type Source #

Methods

from :: RAWState st -> Rep (RAWState st) x Source #

to :: Rep (RAWState st) x -> RAWState st Source #

Generic (RegistryState m) 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Associated Types

type Rep (RegistryState m) :: Type -> Type Source #

Methods

from :: RegistryState m -> Rep (RegistryState m) x Source #

to :: Rep (RegistryState m) x -> RegistryState m Source #

Generic (Resource m) 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Associated Types

type Rep (Resource m) :: Type -> Type Source #

Methods

from :: Resource m -> Rep (Resource m) x Source #

to :: Rep (Resource m) x -> Resource m Source #

Generic (KESKey c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey

Associated Types

type Rep (KESKey c) :: Type -> Type Source #

Methods

from :: KESKey c -> Rep (KESKey c) x Source #

to :: Rep (KESKey c) x -> KESKey c Source #

Generic (KESState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Ledger.HotKey

Associated Types

type Rep (KESState c) :: Type -> Type Source #

Methods

from :: KESState c -> Rep (KESState c) x Source #

to :: Rep (KESState c) x -> KESState c Source #

Generic (PraosIsLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosIsLeader c) :: Type -> Type Source #

Methods

from :: PraosIsLeader c -> Rep (PraosIsLeader c) x Source #

to :: Rep (PraosIsLeader c) x -> PraosIsLeader c Source #

Generic (PraosToSign c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosToSign c) :: Type -> Type Source #

Methods

from :: PraosToSign c -> Rep (PraosToSign c) x Source #

to :: Rep (PraosToSign c) x -> PraosToSign c Source #

Generic (TestAddress addr) 
Instance details

Defined in Ouroboros.Network.Snocket

Associated Types

type Rep (TestAddress addr) :: Type -> Type Source #

Methods

from :: TestAddress addr -> Rep (TestAddress addr) x Source #

to :: Rep (TestAddress addr) x -> TestAddress addr Source #

Generic (EvaluationResult a) 
Instance details

Defined in PlutusCore.Evaluation.Result

Associated Types

type Rep (EvaluationResult a) :: Type -> Type Source #

Methods

from :: EvaluationResult a -> Rep (EvaluationResult a) x Source #

to :: Rep (EvaluationResult a) x -> EvaluationResult a Source #

Generic (BuiltinCostModelBase f) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep (BuiltinCostModelBase f) :: Type -> Type Source #

Methods

from :: BuiltinCostModelBase f -> Rep (BuiltinCostModelBase f) x Source #

to :: Rep (BuiltinCostModelBase f) x -> BuiltinCostModelBase f Source #

Generic (CostingFun model) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep (CostingFun model) :: Type -> Type Source #

Methods

from :: CostingFun model -> Rep (CostingFun model) x Source #

to :: Rep (CostingFun model) x -> CostingFun model Source #

Generic (LR a) 
Instance details

Defined in PlutusCore.Eq

Associated Types

type Rep (LR a) :: Type -> Type Source #

Methods

from :: LR a -> Rep (LR a) x Source #

to :: Rep (LR a) x -> LR a Source #

Generic (RL a) 
Instance details

Defined in PlutusCore.Eq

Associated Types

type Rep (RL a) :: Type -> Type Source #

Methods

from :: RL a -> Rep (RL a) x Source #

to :: Rep (RL a) x -> RL a Source #

Generic (CekExTally fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep (CekExTally fun) :: Type -> Type Source #

Methods

from :: CekExTally fun -> Rep (CekExTally fun) x Source #

to :: Rep (CekExTally fun) x -> CekExTally fun Source #

Generic (ExBudgetCategory fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep (ExBudgetCategory fun) :: Type -> Type Source #

Methods

from :: ExBudgetCategory fun -> Rep (ExBudgetCategory fun) x Source #

to :: Rep (ExBudgetCategory fun) x -> ExBudgetCategory fun Source #

Generic (LinearTransform d) 
Instance details

Defined in Statistics.Distribution.Transform

Associated Types

type Rep (LinearTransform d) :: Type -> Type Source #

Methods

from :: LinearTransform d -> Rep (LinearTransform d) x Source #

to :: Rep (LinearTransform d) x -> LinearTransform d Source #

Generic (Window a) 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep (Window a) :: Type -> Type Source #

Methods

from :: Window a -> Rep (Window a) x Source #

to :: Rep (Window a) x -> Window a Source #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (Doc a) :: Type -> Type Source #

Methods

from :: Doc a -> Rep (Doc a) x Source #

to :: Rep (Doc a) x -> Doc a Source #

Generic (SimpleDoc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (SimpleDoc a) :: Type -> Type Source #

Methods

from :: SimpleDoc a -> Rep (SimpleDoc a) x Source #

to :: Rep (SimpleDoc a) x -> SimpleDoc a Source #

Generic (WrappedState state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.Interface

Associated Types

type Rep (WrappedState state) :: Type -> Type Source #

Methods

from :: WrappedState state -> Rep (WrappedState state) x Source #

to :: Rep (WrappedState state) x -> WrappedState state Source #

Generic (Action (WithCrashTolerance state)) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.CrashTolerance

Associated Types

type Rep (Action (WithCrashTolerance state)) :: Type -> Type Source #

Generic (WithCrashTolerance state) Source # 
Instance details

Defined in Plutus.Contract.Test.ContractModel.CrashTolerance

Associated Types

type Rep (WithCrashTolerance state) :: Type -> Type Source #

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type Source #

Methods

from :: Either a b -> Rep (Either a b) x Source #

to :: Rep (Either a b) x -> Either a b Source #

Generic (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type Source #

Methods

from :: V1 p -> Rep (V1 p) x Source #

to :: Rep (V1 p) x -> V1 p Source #

Generic (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type Source #

Methods

from :: U1 p -> Rep (U1 p) x Source #

to :: Rep (U1 p) x -> U1 p Source #

Generic (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type Source #

Methods

from :: (a, b) -> Rep (a, b) x Source #

to :: Rep (a, b) x -> (a, b) Source #

Generic (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type Source #

Methods

from :: Arg a b -> Rep (Arg a b) x Source #

to :: Rep (Arg a b) x -> Arg a b Source #

Generic (WrappedMonad m a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type Source #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type Source #

Methods

from :: Proxy t -> Rep (Proxy t) x Source #

to :: Rep (Proxy t) x -> Proxy t Source #

Generic (Of a b) 
Instance details

Defined in Data.Functor.Of

Associated Types

type Rep (Of a b) :: Type -> Type Source #

Methods

from :: Of a b -> Rep (Of a b) x Source #

to :: Rep (Of a b) x -> Of a b Source #

Generic (NoContentVerb method) 
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep (NoContentVerb method) :: Type -> Type Source #

Methods

from :: NoContentVerb method -> Rep (NoContentVerb method) x Source #

to :: Rep (NoContentVerb method) x -> NoContentVerb method Source #

Generic (Map k v) 
Instance details

Defined in PlutusTx.AssocMap

Associated Types

type Rep (Map k v) :: Type -> Type Source #

Methods

from :: Map k v -> Rep (Map k v) x Source #

to :: Rep (Map k v) x -> Map k v Source #

Generic (BoundedRatio b a) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep (BoundedRatio b a) :: Type -> Type Source #

Methods

from :: BoundedRatio b a -> Rep (BoundedRatio b a) x Source #

to :: Rep (BoundedRatio b a) x -> BoundedRatio b a Source #

Generic (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

type Rep (Hash h a) :: Type -> Type Source #

Methods

from :: Hash h a -> Rep (Hash h a) x Source #

to :: Rep (Hash h a) x -> Hash h a Source #

Generic (WitVKey kr crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type Rep (WitVKey kr crypto) :: Type -> Type Source #

Methods

from :: WitVKey kr crypto -> Rep (WitVKey kr crypto) x Source #

to :: Rep (WitVKey kr crypto) x -> WitVKey kr crypto Source #

Generic (TyVarDecl tyname ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (TyVarDecl tyname ann) :: Type -> Type Source #

Methods

from :: TyVarDecl tyname ann -> Rep (TyVarDecl tyname ann) x Source #

to :: Rep (TyVarDecl tyname ann) x -> TyVarDecl tyname ann Source #

Generic (SymSet t) 
Instance details

Defined in Test.QuickCheck.ContractModel.Internal.Symbolics

Associated Types

type Rep (SymSet t) :: Type -> Type Source #

Methods

from :: SymSet t -> Rep (SymSet t) x Source #

to :: Rep (SymSet t) x -> SymSet t Source #

Generic (ShelleyTip proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyTip proto era) :: Type -> Type Source #

Methods

from :: ShelleyTip proto era -> Rep (ShelleyTip proto era) x Source #

to :: Rep (ShelleyTip proto era) x -> ShelleyTip proto era Source #

Generic (KeyHash discriminator crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (KeyHash discriminator crypto) :: Type -> Type Source #

Methods

from :: KeyHash discriminator crypto -> Rep (KeyHash discriminator crypto) x Source #

to :: Rep (KeyHash discriminator crypto) x -> KeyHash discriminator crypto Source #

Generic (Block slot hash) 
Instance details

Defined in Ouroboros.Network.Point

Associated Types

type Rep (Block slot hash) :: Type -> Type Source #

Methods

from :: Block slot hash -> Rep (Block slot hash) x Source #

to :: Rep (Block slot hash) x -> Block slot hash Source #

Generic (Annotated b a) 
Instance details

Defined in Cardano.Binary.Annotated

Associated Types

type Rep (Annotated b a) :: Type -> Type Source #

Methods

from :: Annotated b a -> Rep (Annotated b a) x Source #

to :: Rep (Annotated b a) x -> Annotated b a Source #

Generic (Bimap a b) 
Instance details

Defined in Data.Bimap

Associated Types

type Rep (Bimap a b) :: Type -> Type Source #

Methods

from :: Bimap a b -> Rep (Bimap a b) x Source #

to :: Rep (Bimap a b) x -> Bimap a b Source #

Generic (AbstractHash algo a) 
Instance details

Defined in Cardano.Crypto.Hashing

Associated Types

type Rep (AbstractHash algo a) :: Type -> Type Source #

Methods

from :: AbstractHash algo a -> Rep (AbstractHash algo a) x Source #

to :: Rep (AbstractHash algo a) x -> AbstractHash algo a Source #

Generic (SignedKES v a) 
Instance details

Defined in Cardano.Crypto.KES.Class

Associated Types

type Rep (SignedKES v a) :: Type -> Type Source #

Methods

from :: SignedKES v a -> Rep (SignedKES v a) x Source #

to :: Rep (SignedKES v a) x -> SignedKES v a Source #

Generic (PraosFields c toSign) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosFields c toSign) :: Type -> Type Source #

Methods

from :: PraosFields c toSign -> Rep (PraosFields c toSign) x Source #

to :: Rep (PraosFields c toSign) x -> PraosFields c toSign Source #

Generic (VKey kd crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (VKey kd crypto) :: Type -> Type Source #

Methods

from :: VKey kd crypto -> Rep (VKey kd crypto) x Source #

to :: Rep (VKey kd crypto) x -> VKey kd crypto Source #

Generic (PParams' f era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Associated Types

type Rep (PParams' f era) :: Type -> Type Source #

Methods

from :: PParams' f era -> Rep (PParams' f era) x Source #

to :: Rep (PParams' f era) x -> PParams' f era Source #

Generic (PParams' f era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Associated Types

type Rep (PParams' f era) :: Type -> Type Source #

Methods

from :: PParams' f era -> Rep (PParams' f era) x Source #

to :: Rep (PParams' f era) x -> PParams' f era Source #

Generic (Credential kr crypto) 
Instance details

Defined in Cardano.Ledger.Credential

Associated Types

type Rep (Credential kr crypto) :: Type -> Type Source #

Methods

from :: Credential kr crypto -> Rep (Credential kr crypto) x Source #

to :: Rep (Credential kr crypto) x -> Credential kr crypto Source #

Generic (Block h era) 
Instance details

Defined in Cardano.Ledger.Block

Associated Types

type Rep (Block h era) :: Type -> Type Source #

Methods

from :: Block h era -> Rep (Block h era) x Source #

to :: Rep (Block h era) x -> Block h era Source #

Generic (Current f blk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep (Current f blk) :: Type -> Type Source #

Methods

from :: Current f blk -> Rep (Current f blk) x Source #

to :: Rep (Current f blk) x -> Current f blk Source #

Generic (WithMuxBearer peerid a) 
Instance details

Defined in Network.Mux.Trace

Associated Types

type Rep (WithMuxBearer peerid a) :: Type -> Type Source #

Methods

from :: WithMuxBearer peerid a -> Rep (WithMuxBearer peerid a) x Source #

to :: Rep (WithMuxBearer peerid a) x -> WithMuxBearer peerid a Source #

Generic (TPraosFields c toSign) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (TPraosFields c toSign) :: Type -> Type Source #

Methods

from :: TPraosFields c toSign -> Rep (TPraosFields c toSign) x Source #

to :: Rep (TPraosFields c toSign) x -> TPraosFields c toSign Source #

Generic (PParams' f era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

type Rep (PParams' f era) :: Type -> Type Source #

Methods

from :: PParams' f era -> Rep (PParams' f era) x Source #

to :: Rep (PParams' f era) x -> PParams' f era Source #

Era era => Generic (WitnessSetHKD Identity era) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx

Associated Types

type Rep (WitnessSetHKD Identity era) :: Type -> Type Source #

Methods

from :: WitnessSetHKD Identity era -> Rep (WitnessSetHKD Identity era) x Source #

to :: Rep (WitnessSetHKD Identity era) x -> WitnessSetHKD Identity era Source #

Generic (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseError s e) :: Type -> Type Source #

Methods

from :: ParseError s e -> Rep (ParseError s e) x Source #

to :: Rep (ParseError s e) x -> ParseError s e Source #

Generic (State s e) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (State s e) :: Type -> Type Source #

Methods

from :: State s e -> Rep (State s e) x Source #

to :: Rep (State s e) x -> State s e Source #

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) :: Type -> Type Source #

Methods

from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x Source #

to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e Source #

Generic (ErrorWithCause err cause) 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep (ErrorWithCause err cause) :: Type -> Type Source #

Methods

from :: ErrorWithCause err cause -> Rep (ErrorWithCause err cause) x Source #

to :: Rep (ErrorWithCause err cause) x -> ErrorWithCause err cause Source #

Generic (FingerTree v a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (FingerTree v a) :: Type -> Type Source #

Methods

from :: FingerTree v a -> Rep (FingerTree v a) x Source #

to :: Rep (FingerTree v a) x -> FingerTree v a Source #

Generic (PrimaryKey AddressRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey AddressRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey AddressRowT f -> Rep (PrimaryKey AddressRowT f) x Source #

to :: Rep (PrimaryKey AddressRowT f) x -> PrimaryKey AddressRowT f Source #

Generic (PrimaryKey AssetClassRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey AssetClassRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey AssetClassRowT f -> Rep (PrimaryKey AssetClassRowT f) x Source #

to :: Rep (PrimaryKey AssetClassRowT f) x -> PrimaryKey AssetClassRowT f Source #

Generic (PrimaryKey DatumRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey DatumRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey DatumRowT f -> Rep (PrimaryKey DatumRowT f) x Source #

to :: Rep (PrimaryKey DatumRowT f) x -> PrimaryKey DatumRowT f Source #

Generic (PrimaryKey RedeemerRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey RedeemerRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey RedeemerRowT f -> Rep (PrimaryKey RedeemerRowT f) x Source #

to :: Rep (PrimaryKey RedeemerRowT f) x -> PrimaryKey RedeemerRowT f Source #

Generic (PrimaryKey ScriptRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey ScriptRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey ScriptRowT f -> Rep (PrimaryKey ScriptRowT f) x Source #

to :: Rep (PrimaryKey ScriptRowT f) x -> PrimaryKey ScriptRowT f Source #

Generic (PrimaryKey TipRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey TipRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey TipRowT f -> Rep (PrimaryKey TipRowT f) x Source #

to :: Rep (PrimaryKey TipRowT f) x -> PrimaryKey TipRowT f Source #

Generic (PrimaryKey TxRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey TxRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey TxRowT f -> Rep (PrimaryKey TxRowT f) x Source #

to :: Rep (PrimaryKey TxRowT f) x -> PrimaryKey TxRowT f Source #

Generic (PrimaryKey UnmatchedInputRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey UnmatchedInputRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey UnmatchedInputRowT f -> Rep (PrimaryKey UnmatchedInputRowT f) x Source #

to :: Rep (PrimaryKey UnmatchedInputRowT f) x -> PrimaryKey UnmatchedInputRowT f Source #

Generic (PrimaryKey UnspentOutputRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey UnspentOutputRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey UnspentOutputRowT f -> Rep (PrimaryKey UnspentOutputRowT f) x Source #

to :: Rep (PrimaryKey UnspentOutputRowT f) x -> PrimaryKey UnspentOutputRowT f Source #

Generic (PrimaryKey UtxoRowT f) 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type Rep (PrimaryKey UtxoRowT f) :: Type -> Type Source #

Methods

from :: PrimaryKey UtxoRowT f -> Rep (PrimaryKey UtxoRowT f) x Source #

to :: Rep (PrimaryKey UtxoRowT f) x -> PrimaryKey UtxoRowT f Source #

Generic (TxConstraints i o) 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (TxConstraints i o) :: Type -> Type Source #

Methods

from :: TxConstraints i o -> Rep (TxConstraints i o) x Source #

to :: Rep (TxConstraints i o) x -> TxConstraints i o Source #

Generic (Container b a) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (Container b a) :: Type -> Type Source #

Methods

from :: Container b a -> Rep (Container b a) x Source #

to :: Rep (Container b a) x -> Container b a Source #

Generic (EvaluationError user internal) 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep (EvaluationError user internal) :: Type -> Type Source #

Methods

from :: EvaluationError user internal -> Rep (EvaluationError user internal) x Source #

to :: Rep (EvaluationError user internal) x -> EvaluationError user internal Source #

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) :: Type -> Type Source #

Methods

from :: Cofree f a -> Rep (Cofree f a) x Source #

to :: Rep (Cofree f a) x -> Cofree f a Source #

Generic (KeyPair kd crypto) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (KeyPair kd crypto) :: Type -> Type Source #

Methods

from :: KeyPair kd crypto -> Rep (KeyPair kd crypto) x Source #

to :: Rep (KeyPair kd crypto) x -> KeyPair kd crypto Source #

Generic (CertifiedVRF v a) 
Instance details

Defined in Cardano.Crypto.VRF.Class

Associated Types

type Rep (CertifiedVRF v a) :: Type -> Type Source #

Methods

from :: CertifiedVRF v a -> Rep (CertifiedVRF v a) x Source #

to :: Rep (CertifiedVRF v a) x -> CertifiedVRF v a Source #

Generic (SignedDSIGN v a) 
Instance details

Defined in Cardano.Crypto.DSIGN.Class

Associated Types

type Rep (SignedDSIGN v a) :: Type -> Type Source #

Methods

from :: SignedDSIGN v a -> Rep (SignedDSIGN v a) x Source #

to :: Rep (SignedDSIGN v a) x -> SignedDSIGN v a Source #

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) :: Type -> Type Source #

Methods

from :: Either a b -> Rep (Either a b) x Source #

to :: Rep (Either a b) x -> Either a b Source #

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep (Pair a b) :: Type -> Type Source #

Methods

from :: Pair a b -> Rep (Pair a b) x Source #

to :: Rep (Pair a b) x -> Pair a b Source #

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

type Rep (These a b) :: Type -> Type Source #

Methods

from :: These a b -> Rep (These a b) x Source #

to :: Rep (These a b) x -> These a b Source #

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

type Rep (These a b) :: Type -> Type Source #

Methods

from :: These a b -> Rep (These a b) x Source #

to :: Rep (These a b) x -> These a b Source #

Generic (AdjacencyMap e a) 
Instance details

Defined in Algebra.Graph.Labelled.AdjacencyMap

Associated Types

type Rep (AdjacencyMap e a) :: Type -> Type Source #

Methods

from :: AdjacencyMap e a -> Rep (AdjacencyMap e a) x Source #

to :: Rep (AdjacencyMap e a) x -> AdjacencyMap e a Source #

Generic (Graph e a) 
Instance details

Defined in Algebra.Graph.Labelled

Associated Types

type Rep (Graph e a) :: Type -> Type Source #

Methods

from :: Graph e a -> Rep (Graph e a) x Source #

to :: Rep (Graph e a) x -> Graph e a Source #

Generic (ErrorContainer b e) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (ErrorContainer b e) :: Type -> Type Source #

Methods

from :: ErrorContainer b e -> Rep (ErrorContainer b e) x Source #

to :: Rep (ErrorContainer b e) x -> ErrorContainer b e Source #

Generic (Unit f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Unit f) :: Type -> Type Source #

Methods

from :: Unit f -> Rep (Unit f) x Source #

to :: Rep (Unit f) x -> Unit f Source #

Generic (Void f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Void f) :: Type -> Type Source #

Methods

from :: Void f -> Rep (Void f) x Source #

to :: Rep (Void f) x -> Void f Source #

Generic (ListN n a) 
Instance details

Defined in Basement.Sized.List

Associated Types

type Rep (ListN n a) :: Type -> Type Source #

Methods

from :: ListN n a -> Rep (ListN n a) x Source #

to :: Rep (ListN n a) x -> ListN n a Source #

Generic (Validation e a) 
Instance details

Defined in Validation

Associated Types

type Rep (Validation e a) :: Type -> Type Source #

Methods

from :: Validation e a -> Rep (Validation e a) x Source #

to :: Rep (Validation e a) x -> Validation e a Source #

Generic (SearchResult v a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (SearchResult v a) :: Type -> Type Source #

Methods

from :: SearchResult v a -> Rep (SearchResult v a) x Source #

to :: Rep (SearchResult v a) x -> SearchResult v a Source #

Generic (ViewL s a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (ViewL s a) :: Type -> Type Source #

Methods

from :: ViewL s a -> Rep (ViewL s a) x Source #

to :: Rep (ViewL s a) x -> ViewL s a Source #

Generic (ViewR s a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (ViewR s a) :: Type -> Type Source #

Methods

from :: ViewR s a -> Rep (ViewR s a) x Source #

to :: Rep (ViewR s a) x -> ViewR s a Source #

Generic (Node v a) 
Instance details

Defined in Data.FingerTree

Associated Types

type Rep (Node v a) :: Type -> Type Source #

Methods

from :: Node v a -> Rep (Node v a) x Source #

to :: Rep (Node v a) x -> Node v a Source #

Generic (Tuple2 a b) 
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep (Tuple2 a b) :: Type -> Type Source #

Methods

from :: Tuple2 a b -> Rep (Tuple2 a b) x Source #

to :: Rep (Tuple2 a b) x -> Tuple2 a b Source #

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) :: Type -> Type Source #

Methods

from :: Free f a -> Rep (Free f a) x Source #

to :: Rep (Free f a) x -> Free f a Source #

Generic (ListT m a) 
Instance details

Defined in ListT

Associated Types

type Rep (ListT m a) :: Type -> Type Source #

Methods

from :: ListT m a -> Rep (ListT m a) x Source #

to :: Rep (ListT m a) x -> ListT m a Source #

Generic (FirstToFinish m a) 
Instance details

Defined in Data.Monoid.Synchronisation

Associated Types

type Rep (FirstToFinish m a) :: Type -> Type Source #

Methods

from :: FirstToFinish m a -> Rep (FirstToFinish m a) x Source #

to :: Rep (FirstToFinish m a) x -> FirstToFinish m a Source #

Generic (LastToFinish m a) 
Instance details

Defined in Data.Monoid.Synchronisation

Associated Types

type Rep (LastToFinish m a) :: Type -> Type Source #

Methods

from :: LastToFinish m a -> Rep (LastToFinish m a) x Source #

to :: Rep (LastToFinish m a) x -> LastToFinish m a Source #

Generic (LastToFinishM m a) 
Instance details

Defined in Data.Monoid.Synchronisation

Associated Types

type Rep (LastToFinishM m a) :: Type -> Type Source #

Methods

from :: LastToFinishM m a -> Rep (LastToFinishM m a) x Source #

to :: Rep (LastToFinishM m a) x -> LastToFinishM m a Source #

Generic (PBftFields c toSign) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftFields c toSign) :: Type -> Type Source #

Methods

from :: PBftFields c toSign -> Rep (PBftFields c toSign) x Source #

to :: Rep (PBftFields c toSign) x -> PBftFields c toSign Source #

Generic (ChainDbEnv m blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (ChainDbEnv m blk) :: Type -> Type Source #

Methods

from :: ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x Source #

to :: Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk Source #

Generic (LgrDB m blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB

Associated Types

type Rep (LgrDB m blk) :: Type -> Type Source #

Methods

from :: LgrDB m blk -> Rep (LgrDB m blk) x Source #

to :: Rep (LgrDB m blk) x -> LgrDB m blk Source #

Generic (ChainDbState m blk) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (ChainDbState m blk) :: Type -> Type Source #

Methods

from :: ChainDbState m blk -> Rep (ChainDbState m blk) x Source #

to :: Rep (ChainDbState m blk) x -> ChainDbState m blk Source #

Generic (TraceChunkValidation blk validateTo) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

Associated Types

type Rep (TraceChunkValidation blk validateTo) :: Type -> Type Source #

Methods

from :: TraceChunkValidation blk validateTo -> Rep (TraceChunkValidation blk validateTo) x Source #

to :: Rep (TraceChunkValidation blk validateTo) x -> TraceChunkValidation blk validateTo Source #

Generic (InternalState blk h) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

Associated Types

type Rep (InternalState blk h) :: Type -> Type Source #

Methods

from :: InternalState blk h -> Rep (InternalState blk h) x Source #

to :: Rep (InternalState blk h) x -> InternalState blk h Source #

Generic (OpenState blk h) 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

Associated Types

type Rep (OpenState blk h) :: Type -> Type Source #

Methods

from :: OpenState blk h -> Rep (OpenState blk h) x Source #

to :: Rep (OpenState blk h) x -> OpenState blk h Source #

Generic (ServerState txid tx) 
Instance details

Defined in Ouroboros.Network.TxSubmission.Inbound

Associated Types

type Rep (ServerState txid tx) :: Type -> Type Source #

Methods

from :: ServerState txid tx -> Rep (ServerState txid tx) x Source #

to :: Rep (ServerState txid tx) x -> ServerState txid tx Source #

Generic (Def var val) 
Instance details

Defined in PlutusCore.MkPlc

Associated Types

type Rep (Def var val) :: Type -> Type Source #

Methods

from :: Def var val -> Rep (Def var val) x Source #

to :: Rep (Def var val) x -> Def var val Source #

Generic (TypeErrorExt uni ann) 
Instance details

Defined in PlutusIR.Error

Associated Types

type Rep (TypeErrorExt uni ann) :: Type -> Type Source #

Methods

from :: TypeErrorExt uni ann -> Rep (TypeErrorExt uni ann) x Source #

to :: Rep (TypeErrorExt uni ann) x -> TypeErrorExt uni ann Source #

Generic (UVarDecl name ann) 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (UVarDecl name ann) :: Type -> Type Source #

Methods

from :: UVarDecl name ann -> Rep (UVarDecl name ann) x Source #

to :: Rep (UVarDecl name ann) x -> UVarDecl name ann Source #

Generic (ListF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (ListF a b) :: Type -> Type Source #

Methods

from :: ListF a b -> Rep (ListF a b) x Source #

to :: Rep (ListF a b) x -> ListF a b Source #

Generic (NonEmptyF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (NonEmptyF a b) :: Type -> Type Source #

Methods

from :: NonEmptyF a b -> Rep (NonEmptyF a b) x Source #

to :: Rep (NonEmptyF a b) x -> NonEmptyF a b Source #

Generic (TreeF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (TreeF a b) :: Type -> Type Source #

Methods

from :: TreeF a b -> Rep (TreeF a b) x Source #

to :: Rep (TreeF a b) x -> TreeF a b Source #

Generic (SearchResult v a) 
Instance details

Defined in Data.FingerTree.Strict

Associated Types

type Rep (SearchResult v a) :: Type -> Type Source #

Methods

from :: SearchResult v a -> Rep (SearchResult v a) x Source #

to :: Rep (SearchResult v a) x -> SearchResult v a Source #

Generic (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type Source #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x Source #

to :: Rep (Rec1 f p) x -> Rec1 f p Source #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type Source #

Methods

from :: URec Char p -> Rep (URec Char p) x Source #

to :: Rep (URec Char p) x -> URec Char p Source #

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type Source #

Methods

from :: URec Double p -> Rep (URec Double p) x Source #

to :: Rep (URec Double p) x -> URec Double p Source #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type Source #

Methods

from :: URec Float p -> Rep (URec Float p) x Source #

to :: Rep (URec Float p) x -> URec Float p Source #

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type Source #

Methods

from :: URec Int p -> Rep (URec Int p) x Source #

to :: Rep (URec Int p) x -> URec Int p Source #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type Source #

Methods

from :: URec Word p -> Rep (URec Word p) x Source #

to :: Rep (URec Word p) x -> URec Word p Source #

Generic (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type Source #

Methods

from :: (a, b, c) -> Rep (a, b, c) x Source #

to :: Rep (a, b, c) x -> (a, b, c) Source #

Generic (WrappedArrow a b c)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type Source #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x Source #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c Source #

Generic (Kleisli m a b)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type Source #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x Source #

to :: Rep (Kleisli m a b) x -> Kleisli m a b Source #

Generic (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type Source #

Methods

from :: Const a b -> Rep (Const a b) x Source #

to :: Rep (Const a b) x -> Const a b Source #

Generic (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type Source #

Methods

from :: Ap f a -> Rep (Ap f a) x Source #

to :: Rep (Ap f a) x -> Ap f a Source #

Generic (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type Source #

Methods

from :: Alt f a -> Rep (Alt f a) x Source #

to :: Rep (Alt f a) x -> Alt f a Source #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type Source #

Methods

from :: Tagged s b -> Rep (Tagged s b) x Source #

to :: Rep (Tagged s b) x -> Tagged s b Source #

Generic (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (K a b) :: Type -> Type Source #

Methods

from :: K a b -> Rep (K a b) x Source #

to :: Rep (K a b) x -> K a b Source #

Generic (Type tyname uni ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Type tyname uni ann) :: Type -> Type Source #

Methods

from :: Type tyname uni ann -> Rep (Type tyname uni ann) x Source #

to :: Rep (Type tyname uni ann) x -> Type tyname uni ann Source #

Generic (WithBlockNo f a) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.ChainSel

Associated Types

type Rep (WithBlockNo f a) :: Type -> Type Source #

Methods

from :: WithBlockNo f a -> Rep (WithBlockNo f a) x Source #

to :: Rep (WithBlockNo f a) x -> WithBlockNo f a Source #

Generic (Trip coin ptr pool) 
Instance details

Defined in Data.UMap

Associated Types

type Rep (Trip coin ptr pool) :: Type -> Type Source #

Methods

from :: Trip coin ptr pool -> Rep (Trip coin ptr pool) x Source #

to :: Rep (Trip coin ptr pool) x -> Trip coin ptr pool Source #

Generic (Error uni fun ann) 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (Error uni fun ann) :: Type -> Type Source #

Methods

from :: Error uni fun ann -> Rep (Error uni fun ann) x Source #

to :: Rep (Error uni fun ann) x -> Error uni fun ann Source #

Generic (AnchoredSeq v a b) 
Instance details

Defined in Ouroboros.Network.AnchoredSeq

Associated Types

type Rep (AnchoredSeq v a b) :: Type -> Type Source #

Methods

from :: AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x Source #

to :: Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b Source #

Generic (KVVector kv vv a) 
Instance details

Defined in Data.VMap.KVVector

Associated Types

type Rep (KVVector kv vv a) :: Type -> Type Source #

Methods

from :: KVVector kv vv a -> Rep (KVVector kv vv a) x Source #

to :: Rep (KVVector kv vv a) x -> KVVector kv vv a Source #

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

type Rep (These1 f g a) :: Type -> Type Source #

Methods

from :: These1 f g a -> Rep (These1 f g a) x Source #

to :: Rep (These1 f g a) x -> These1 f g a Source #

Generic (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Associated Types

type Rep (Fix p a) :: Type -> Type Source #

Methods

from :: Fix p a -> Rep (Fix p a) x Source #

to :: Rep (Fix p a) x -> Fix p a Source #

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) :: Type -> Type Source #

Methods

from :: Join p a -> Rep (Join p a) x Source #

to :: Rep (Join p a) x -> Join p a Source #

Generic (Tuple3 a b c) 
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep (Tuple3 a b c) :: Type -> Type Source #

Methods

from :: Tuple3 a b c -> Rep (Tuple3 a b c) x Source #

to :: Rep (Tuple3 a b c) x -> Tuple3 a b c Source #

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep (CofreeF f a b) :: Type -> Type Source #

Methods

from :: CofreeF f a b -> Rep (CofreeF f a b) x Source #

to :: Rep (CofreeF f a b) x -> CofreeF f a b Source #

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

type Rep (FreeF f a b) :: Type -> Type Source #

Methods

from :: FreeF f a b -> Rep (FreeF f a b) x Source #

to :: Rep (FreeF f a b) x -> FreeF f a b Source #

Generic (MeasuredWith v a b) 
Instance details

Defined in Ouroboros.Network.AnchoredSeq

Associated Types

type Rep (MeasuredWith v a b) :: Type -> Type Source #

Methods

from :: MeasuredWith v a b -> Rep (MeasuredWith v a b) x Source #

to :: Rep (MeasuredWith v a b) x -> MeasuredWith v a b Source #

Generic (IteratorState m blk b) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Iterator

Associated Types

type Rep (IteratorState m blk b) :: Type -> Type Source #

Methods

from :: IteratorState m blk b -> Rep (IteratorState m blk b) x Source #

to :: Rep (IteratorState m blk b) x -> IteratorState m blk b Source #

Generic (FollowerState m blk b) 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

Associated Types

type Rep (FollowerState m blk b) :: Type -> Type Source #

Methods

from :: FollowerState m blk b -> Rep (FollowerState m blk b) x Source #

to :: Rep (FollowerState m blk b) x -> FollowerState m blk b Source #

Generic (IteratorState m blk h) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Iterator

Associated Types

type Rep (IteratorState m blk h) :: Type -> Type Source #

Methods

from :: IteratorState m blk h -> Rep (IteratorState m blk h) x Source #

to :: Rep (IteratorState m blk h) x -> IteratorState m blk h Source #

Generic (IteratorStateOrExhausted m hash h) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Iterator

Associated Types

type Rep (IteratorStateOrExhausted m hash h) :: Type -> Type Source #

Methods

from :: IteratorStateOrExhausted m hash h -> Rep (IteratorStateOrExhausted m hash h) x Source #

to :: Rep (IteratorStateOrExhausted m hash h) x -> IteratorStateOrExhausted m hash h Source #

Generic (InternalState m blk h) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State

Associated Types

type Rep (InternalState m blk h) :: Type -> Type Source #

Methods

from :: InternalState m blk h -> Rep (InternalState m blk h) x Source #

to :: Rep (InternalState m blk h) x -> InternalState m blk h Source #

Generic (OpenState m blk h) 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State

Associated Types

type Rep (OpenState m blk h) :: Type -> Type Source #

Methods

from :: OpenState m blk h -> Rep (OpenState m blk h) x Source #

to :: Rep (OpenState m blk h) x -> OpenState m blk h Source #

Generic (TyDecl tyname uni ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (TyDecl tyname uni ann) :: Type -> Type Source #

Methods

from :: TyDecl tyname uni ann -> Rep (TyDecl tyname uni ann) x Source #

to :: Rep (TyDecl tyname uni ann) x -> TyDecl tyname uni ann Source #

Generic (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type Source #

Methods

from :: K1 i c p -> Rep (K1 i c p) x Source #

to :: Rep (K1 i c p) x -> K1 i c p Source #

Generic ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type Source #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x Source #

to :: Rep ((f :+: g) p) x -> (f :+: g) p Source #

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type Source #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x Source #

to :: Rep ((f :*: g) p) x -> (f :*: g) p Source #

Generic (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type Source #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x Source #

to :: Rep (a, b, c, d) x -> (a, b, c, d) Source #

Generic (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type Source #

Methods

from :: Product f g a -> Rep (Product f g a) x Source #

to :: Rep (Product f g a) x -> Product f g a Source #

Generic (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type Source #

Methods

from :: Sum f g a -> Rep (Sum f g a) x Source #

to :: Rep (Sum f g a) x -> Sum f g a Source #

Generic (ContractInstanceState w s e a) 
Instance details

Defined in Plutus.Trace.Emulator.Types

Associated Types

type Rep (ContractInstanceState w s e a) :: Type -> Type Source #

Methods

from :: ContractInstanceState w s e a -> Rep (ContractInstanceState w s e a) x Source #

to :: Rep (ContractInstanceState w s e a) x -> ContractInstanceState w s e a Source #

Generic (StreamBody' mods framing contentType a) 
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep (StreamBody' mods framing contentType a) :: Type -> Type Source #

Methods

from :: StreamBody' mods framing contentType a -> Rep (StreamBody' mods framing contentType a) x Source #

to :: Rep (StreamBody' mods framing contentType a) x -> StreamBody' mods framing contentType a Source #

Generic (Program name uni fun ann) 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (Program name uni fun ann) :: Type -> Type Source #

Methods

from :: Program name uni fun ann -> Rep (Program name uni fun ann) x Source #

to :: Rep (Program name uni fun ann) x -> Program name uni fun ann Source #

Generic (Term name uni fun ann) 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (Term name uni fun ann) :: Type -> Type Source #

Methods

from :: Term name uni fun ann -> Rep (Term name uni fun ann) x Source #

to :: Rep (Term name uni fun ann) x -> Term name uni fun ann Source #

Generic (Product2 f g x y) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Functors

Associated Types

type Rep (Product2 f g x y) :: Type -> Type Source #

Methods

from :: Product2 f g x y -> Rep (Product2 f g x y) x0 Source #

to :: Rep (Product2 f g x y) x0 -> Product2 f g x y Source #

Generic (UMap coin cred pool ptr) 
Instance details

Defined in Data.UMap

Associated Types

type Rep (UMap coin cred pool ptr) :: Type -> Type Source #

Methods

from :: UMap coin cred pool ptr -> Rep (UMap coin cred pool ptr) x Source #

to :: Rep (UMap coin cred pool ptr) x -> UMap coin cred pool ptr Source #

Generic (VMap kv vv k v) 
Instance details

Defined in Data.VMap

Associated Types

type Rep (VMap kv vv k v) :: Type -> Type Source #

Methods

from :: VMap kv vv k v -> Rep (VMap kv vv k v) x Source #

to :: Rep (VMap kv vv k v) x -> VMap kv vv k v Source #

Generic (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (TypeError term uni fun ann) :: Type -> Type Source #

Methods

from :: TypeError term uni fun ann -> Rep (TypeError term uni fun ann) x Source #

to :: Rep (TypeError term uni fun ann) x -> TypeError term uni fun ann Source #

Generic (Tuple4 a b c d) 
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep (Tuple4 a b c d) :: Type -> Type Source #

Methods

from :: Tuple4 a b c d -> Rep (Tuple4 a b c d) x Source #

to :: Rep (Tuple4 a b c d) x -> Tuple4 a b c d Source #

Generic (MachineParameters machinecosts term uni fun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.MachineParameters

Associated Types

type Rep (MachineParameters machinecosts term uni fun) :: Type -> Type Source #

Methods

from :: MachineParameters machinecosts term uni fun -> Rep (MachineParameters machinecosts term uni fun) x Source #

to :: Rep (MachineParameters machinecosts term uni fun) x -> MachineParameters machinecosts term uni fun Source #

Generic (Subst name uni fun a) 
Instance details

Defined in UntypedPlutusCore.Transform.Inline

Associated Types

type Rep (Subst name uni fun a) :: Type -> Type Source #

Methods

from :: Subst name uni fun a -> Rep (Subst name uni fun a) x Source #

to :: Rep (Subst name uni fun a) x -> Subst name uni fun a Source #

Generic (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type Source #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x Source #

to :: Rep (M1 i c f p) x -> M1 i c f p Source #

Generic ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type Source #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x Source #

to :: Rep ((f :.: g) p) x -> (f :.: g) p Source #

Generic (a, b, c, d, e)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x Source #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) Source #

Generic (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type Source #

Methods

from :: Compose f g a -> Rep (Compose f g a) x Source #

to :: Rep (Compose f g a) x -> Compose f g a Source #

Generic (ResumableResult w e i o a) 
Instance details

Defined in Plutus.Contract.Types

Associated Types

type Rep (ResumableResult w e i o a) :: Type -> Type Source #

Methods

from :: ResumableResult w e i o a -> Rep (ResumableResult w e i o a) x Source #

to :: Rep (ResumableResult w e i o a) x -> ResumableResult w e i o a Source #

Generic (Program tyname name uni fun ann) 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep (Program tyname name uni fun ann) :: Type -> Type Source #

Methods

from :: Program tyname name uni fun ann -> Rep (Program tyname name uni fun ann) x Source #

to :: Rep (Program tyname name uni fun ann) x -> Program tyname name uni fun ann Source #

Generic (Verb method statusCode contentTypes a) 
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep (Verb method statusCode contentTypes a) :: Type -> Type Source #

Methods

from :: Verb method statusCode contentTypes a -> Rep (Verb method statusCode contentTypes a) x Source #

to :: Rep (Verb method statusCode contentTypes a) x -> Verb method statusCode contentTypes a Source #

Generic ((f :.: g) p) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep ((f :.: g) p) :: Type -> Type Source #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x Source #

to :: Rep ((f :.: g) p) x -> (f :.: g) p Source #

Generic (Term tyname name uni fun a) 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep (Term tyname name uni fun a) :: Type -> Type Source #

Methods

from :: Term tyname name uni fun a -> Rep (Term tyname name uni fun a) x Source #

to :: Rep (Term tyname name uni fun a) x -> Term tyname name uni fun a Source #

Generic (Datatype tyname name uni fun a) 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep (Datatype tyname name uni fun a) :: Type -> Type Source #

Methods

from :: Datatype tyname name uni fun a -> Rep (Datatype tyname name uni fun a) x Source #

to :: Rep (Datatype tyname name uni fun a) x -> Datatype tyname name uni fun a Source #

Generic (Binding tyname name uni fun a) 
Instance details

Defined in PlutusIR.Core.Type

Associated Types

type Rep (Binding tyname name uni fun a) :: Type -> Type Source #

Methods

from :: Binding tyname name uni fun a -> Rep (Binding tyname name uni fun a) x Source #

to :: Rep (Binding tyname name uni fun a) x -> Binding tyname name uni fun a Source #

Generic (Term tyname name uni fun ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Term tyname name uni fun ann) :: Type -> Type Source #

Methods

from :: Term tyname name uni fun ann -> Rep (Term tyname name uni fun ann) x Source #

to :: Rep (Term tyname name uni fun ann) x -> Term tyname name uni fun ann Source #

Generic (Program tyname name uni fun ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Program tyname name uni fun ann) :: Type -> Type Source #

Methods

from :: Program tyname name uni fun ann -> Rep (Program tyname name uni fun ann) x Source #

to :: Rep (Program tyname name uni fun ann) x -> Program tyname name uni fun ann Source #

Generic (NormCheckError tyname name uni fun ann) 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (NormCheckError tyname name uni fun ann) :: Type -> Type Source #

Methods

from :: NormCheckError tyname name uni fun ann -> Rep (NormCheckError tyname name uni fun ann) x Source #

to :: Rep (NormCheckError tyname name uni fun ann) x -> NormCheckError tyname name uni fun ann Source #

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) :: Type -> Type Source #

Methods

from :: Clown f a b -> Rep (Clown f a b) x Source #

to :: Rep (Clown f a b) x -> Clown f a b Source #

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) :: Type -> Type Source #

Methods

from :: Flip p a b -> Rep (Flip p a b) x Source #

to :: Rep (Flip p a b) x -> Flip p a b Source #

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) :: Type -> Type Source #

Methods

from :: Joker g a b -> Rep (Joker g a b) x Source #

to :: Rep (Joker g a b) x -> Joker g a b Source #

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) :: Type -> Type Source #

Methods

from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x Source #

to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b Source #

Generic (Subst tyname name uni fun a) 
Instance details

Defined in PlutusIR.Transform.Inline

Associated Types

type Rep (Subst tyname name uni fun a) :: Type -> Type Source #

Methods

from :: Subst tyname name uni fun a -> Rep (Subst tyname name uni fun a) x Source #

to :: Rep (Subst tyname name uni fun a) x -> Subst tyname name uni fun a Source #

Generic (BindingGrp tyname name uni fun a) 
Instance details

Defined in PlutusIR.Transform.LetFloat

Associated Types

type Rep (BindingGrp tyname name uni fun a) :: Type -> Type Source #

Methods

from :: BindingGrp tyname name uni fun a -> Rep (BindingGrp tyname name uni fun a) x Source #

to :: Rep (BindingGrp tyname name uni fun a) x -> BindingGrp tyname name uni fun a Source #

Generic (a, b, c, d, e, f)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x Source #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) Source #

Generic (Stream method status framing contentType a) 
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep (Stream method status framing contentType a) :: Type -> Type Source #

Methods

from :: Stream method status framing contentType a -> Rep (Stream method status framing contentType a) x Source #

to :: Rep (Stream method status framing contentType a) x -> Stream method status framing contentType a Source #

Generic (VarDecl tyname name uni fun ann) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (VarDecl tyname name uni fun ann) :: Type -> Type Source #

Methods

from :: VarDecl tyname name uni fun ann -> Rep (VarDecl tyname name uni fun ann) x Source #

to :: Rep (VarDecl tyname name uni fun ann) x -> VarDecl tyname name uni fun ann Source #

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) :: Type -> Type Source #

Methods

from :: Product f g a b -> Rep (Product f g a b) x Source #

to :: Rep (Product f g a b) x -> Product f g a b Source #

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) :: Type -> Type Source #

Methods

from :: Sum p q a b -> Rep (Sum p q a b) x Source #

to :: Rep (Sum p q a b) x -> Sum p q a b Source #

Generic (a, b, c, d, e, f, g)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type Source #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x Source #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) Source #

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) :: Type -> Type Source #

Methods

from :: Tannen f p a b -> Rep (Tannen f p a b) x Source #

to :: Rep (Tannen f p a b) x -> Tannen f p a b Source #

Generic (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) :: Type -> Type Source #

Methods

from :: Biff p f g a b -> Rep (Biff p f g a b) x Source #

to :: Rep (Biff p f g a b) x -> Biff p f g a b Source #

Utils

fromAssetId :: AssetId -> AssetClass Source #

toAssetId :: AssetClass -> AssetId Source #

Orphan instances

HasSymbolics Wallet Source # 
Instance details

Methods

getAllSymbolics :: Wallet -> SymCollectionIndex #

HasSymbolics Value Source # 
Instance details

Methods

getAllSymbolics :: Value -> SymCollectionIndex #

HasSymbolics BuiltinByteString Source # 
Instance details

Methods

getAllSymbolics :: BuiltinByteString -> SymCollectionIndex #

SymValueLike Ada Source # 
Instance details

Methods

toSymValue :: Ada -> SymValue #

SymValueLike Value Source # 
Instance details

Methods

toSymValue :: Value -> SymValue #

TokenLike AssetClass Source # 
Instance details

Methods

symAssetIdValueOf :: SymValue -> AssetClass -> Quantity #

symAssetIdValue :: AssetClass -> Quantity -> SymValue #

HasVariables BuiltinByteString Source # 
Instance details

Methods

getAllVariables :: BuiltinByteString -> Set (Any Var)