{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Cardano.QueryHF () where
import Data.Functor.Product
import Data.SOP.BasicFunctors
import Data.SOP.Constraint
import Data.SOP.Index
import Data.SOP.Strict
import Data.Singletons
import NoThunks.Class
import Ouroboros.Consensus.Byron.Ledger
import Ouroboros.Consensus.Byron.Node ()
import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Cardano.CanHardFork
import Ouroboros.Consensus.Cardano.Ledger
import Ouroboros.Consensus.HardFork.Combinator
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Ledger.Query
import Ouroboros.Consensus.Ledger.Tables
import Ouroboros.Consensus.Shelley.HFEras ()
import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node ()
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.TypeFamilyWrappers
newtype FlipBlockQuery footprint result x
= FlipBlockQuery (BlockQuery x footprint result)
answerCardanoQueryHF ::
forall x xs c footprint result m.
( xs ~ CardanoEras c
, CardanoHardForkConstraints c
, All (Compose NoThunks WrapTxOut) xs
, SingI footprint
) =>
( forall blk.
IsShelleyBlock blk =>
Index xs blk ->
ExtLedgerCfg blk ->
BlockQuery blk footprint result ->
ReadOnlyForker' m (HardForkBlock xs) ->
m result
) ->
Index xs x ->
ExtLedgerCfg x ->
BlockQuery x footprint result ->
ReadOnlyForker' m (HardForkBlock xs) ->
m result
answerCardanoQueryHF :: forall x (xs :: [*]) c (footprint :: QueryFootprint) result
(m :: * -> *).
(xs ~ CardanoEras c, CardanoHardForkConstraints c,
All (Compose NoThunks WrapTxOut) xs, SingI footprint) =>
(forall blk.
IsShelleyBlock blk =>
Index xs blk
-> ExtLedgerCfg blk
-> BlockQuery blk footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result)
-> Index xs x
-> ExtLedgerCfg x
-> BlockQuery x footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
answerCardanoQueryHF forall blk.
IsShelleyBlock blk =>
Index xs blk
-> ExtLedgerCfg blk
-> BlockQuery blk footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
f Index xs x
idx ExtLedgerCfg x
cfg BlockQuery x footprint result
q ReadOnlyForker' m (HardForkBlock xs)
dlv =
case Sing footprint
forall {k} (a :: k). SingI a => Sing a
sing :: Sing footprint of
SQueryFootprint footprint
Sing footprint
SQFNoTables ->
[Char] -> m result
forall a. HasCallStack => [Char] -> a
error [Char]
"answerCardanoQueryHF: unreachable, this was called with a QFNoTables query"
Sing footprint
_ ->
NS (K (m result)) xs -> CollapseTo NS (m result)
forall (xs :: [*]) a.
SListIN NS xs =>
NS (K a) xs -> CollapseTo NS a
forall k l (h :: (k -> *) -> l -> *) (xs :: l) a.
(HCollapse h, SListIN h xs) =>
h (K a) xs -> CollapseTo h a
hcollapse (NS (K (m result)) xs -> CollapseTo NS (m result))
-> NS (K (m result)) xs -> CollapseTo NS (m result)
forall a b. (a -> b) -> a -> b
$
Prod
NS
(Product ExtLedgerCfg (FlipBlockQuery footprint result)
-.-> K (m result))
xs
-> NS (Product ExtLedgerCfg (FlipBlockQuery footprint result)) xs
-> NS (K (m result)) xs
forall k l (h :: (k -> *) -> l -> *) (f :: k -> *) (g :: k -> *)
(xs :: l).
HAp h =>
Prod h (f -.-> g) xs -> h f xs -> h g xs
forall (f :: * -> *) (g :: * -> *) (xs :: [*]).
Prod NS (f -.-> g) xs -> NS f xs -> NS g xs
hap
( ((Product ExtLedgerCfg (FlipBlockQuery footprint result) ByronBlock
-> K (m result) ByronBlock)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
ByronBlock
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
(f a -> g a) -> (-.->) f g a
Fn ((Product ExtLedgerCfg (FlipBlockQuery footprint result) ByronBlock
-> K (m result) ByronBlock)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
ByronBlock)
-> (Product
ExtLedgerCfg (FlipBlockQuery footprint result) ByronBlock
-> K (m result) ByronBlock)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
ByronBlock
forall a b. (a -> b) -> a -> b
$ \(Pair ExtLedgerCfg ByronBlock
_ (FlipBlockQuery BlockQuery ByronBlock footprint result
q')) -> case BlockQuery ByronBlock footprint result
q' of {})
(-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
ByronBlock
-> NP
(Product ExtLedgerCfg (FlipBlockQuery footprint result)
-.-> K (m result))
(CardanoShelleyEras c)
-> NP
(Product ExtLedgerCfg (FlipBlockQuery footprint result)
-.-> K (m result))
(CardanoEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* Proxy IsShelleyBlock
-> (forall a.
IsShelleyBlock a =>
Index (CardanoShelleyEras c) a
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
a)
-> NP (Index (CardanoShelleyEras c)) (CardanoShelleyEras c)
-> NP
(Product ExtLedgerCfg (FlipBlockQuery footprint result)
-.-> K (m result))
(CardanoShelleyEras c)
forall {k} {l} (h :: (k -> *) -> l -> *) (c :: k -> Constraint)
(xs :: l) (proxy :: (k -> Constraint) -> *) (f :: k -> *)
(f' :: k -> *).
(AllN (Prod h) c xs, HAp h) =>
proxy c
-> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs
hcmap
(forall {k} (t :: k). Proxy t
forall (t :: * -> Constraint). Proxy t
Proxy @(IsShelleyBlock))
(\Index (CardanoShelleyEras c) a
idx' -> (Product ExtLedgerCfg (FlipBlockQuery footprint result) a
-> K (m result) a)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
(f a -> g a) -> (-.->) f g a
Fn ((Product ExtLedgerCfg (FlipBlockQuery footprint result) a
-> K (m result) a)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
a)
-> (Product ExtLedgerCfg (FlipBlockQuery footprint result) a
-> K (m result) a)
-> (-.->)
(Product ExtLedgerCfg (FlipBlockQuery footprint result))
(K (m result))
a
forall a b. (a -> b) -> a -> b
$ \(Pair ExtLedgerCfg a
cfg' (FlipBlockQuery BlockQuery a footprint result
q')) -> m result -> K (m result) a
forall k a (b :: k). a -> K a b
K (m result -> K (m result) a) -> m result -> K (m result) a
forall a b. (a -> b) -> a -> b
$ Index xs a
-> ExtLedgerCfg a
-> BlockQuery a footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
forall blk.
IsShelleyBlock blk =>
Index xs blk
-> ExtLedgerCfg blk
-> BlockQuery blk footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
f (Index (CardanoShelleyEras c) a -> Index xs a
forall {k} (xs :: [k]) (x :: k) (x' :: k) (xs' :: [k]).
(xs ~ (x' : xs')) =>
Index xs' x -> Index xs x
IS Index (CardanoShelleyEras c) a
idx') ExtLedgerCfg a
cfg' BlockQuery a footprint result
q' ReadOnlyForker' m (HardForkBlock xs)
dlv)
NP (Index (CardanoShelleyEras c)) (CardanoShelleyEras c)
forall {k} (xs :: [k]). SListI xs => NP (Index xs) xs
indices
)
(Index xs x
-> Product ExtLedgerCfg (FlipBlockQuery footprint result) x
-> NS (Product ExtLedgerCfg (FlipBlockQuery footprint result)) xs
forall {k} (f :: k -> *) (x :: k) (xs :: [k]).
All Top xs =>
Index xs x -> f x -> NS f xs
injectNS Index xs x
idx (ExtLedgerCfg x
-> FlipBlockQuery footprint result x
-> Product ExtLedgerCfg (FlipBlockQuery footprint result) x
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ExtLedgerCfg x
cfg (BlockQuery x footprint result -> FlipBlockQuery footprint result x
forall (footprint :: QueryFootprint) result x.
BlockQuery x footprint result -> FlipBlockQuery footprint result x
FlipBlockQuery BlockQuery x footprint result
q)))
shelleyCardanoFilter ::
forall proto era c result.
( CardanoHardForkConstraints c
, ShelleyCompatible proto era
) =>
BlockQuery (ShelleyBlock proto era) QFTraverseTables result ->
TxOut (LedgerState (HardForkBlock (CardanoEras c))) ->
Bool
shelleyCardanoFilter :: forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
q = (forall x.
IsShelleyBlock x =>
Index (ByronBlock : CardanoShelleyEras c) x
-> TxOut (LedgerState x) -> Bool)
-> CardanoTxOut c -> Bool
forall r c.
CardanoHardForkConstraints c =>
(forall x.
IsShelleyBlock x =>
Index (CardanoEras c) x -> TxOut (LedgerState x) -> r)
-> CardanoTxOut c -> r
eliminateCardanoTxOut (\Index (ByronBlock : CardanoShelleyEras c) x
_ -> BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (ShelleyBlock Any (ShelleyBlockLedgerEra x)))
-> Bool
forall proto era proto' era' result.
(ShelleyBasedEra era, ShelleyBasedEra era') =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (ShelleyBlock proto' era')) -> Bool
shelleyQFTraverseTablesPredicate BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
q)
instance CardanoHardForkConstraints c => BlockSupportsHFLedgerQuery (CardanoEras c) where
answerBlockQueryHFLookup :: forall (m :: * -> *) x result.
(All SingleEraBlock (CardanoEras c), Monad m) =>
Index (CardanoEras c) x
-> ExtLedgerCfg x
-> BlockQuery x 'QFLookupTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
answerBlockQueryHFLookup =
(forall blk.
IsShelleyBlock blk =>
Index (CardanoEras c) blk
-> ExtLedgerCfg blk
-> BlockQuery blk 'QFLookupTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result)
-> Index (CardanoEras c) x
-> ExtLedgerCfg x
-> BlockQuery x 'QFLookupTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
forall x (xs :: [*]) c (footprint :: QueryFootprint) result
(m :: * -> *).
(xs ~ CardanoEras c, CardanoHardForkConstraints c,
All (Compose NoThunks WrapTxOut) xs, SingI footprint) =>
(forall blk.
IsShelleyBlock blk =>
Index xs blk
-> ExtLedgerCfg blk
-> BlockQuery blk footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result)
-> Index xs x
-> ExtLedgerCfg x
-> BlockQuery x footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
answerCardanoQueryHF
( \Index (CardanoEras c) blk
idx ->
(LedgerTables
(LedgerState
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk)))
KeysMK
-> LedgerTables
(LedgerState (HardForkBlock (CardanoEras c))) KeysMK)
-> (TxOut (LedgerState (HardForkBlock (CardanoEras c)))
-> TxOut (ShelleyBlockLedgerEra blk))
-> (TxIn (LedgerState (HardForkBlock (CardanoEras c))) -> TxIn)
-> ExtLedgerCfg
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
-> BlockQuery
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
'QFLookupTables
result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
forall proto era (m :: * -> *) result blk.
(Monad m, ShelleyCompatible proto era) =>
(LedgerTables (LedgerState (ShelleyBlock proto era)) KeysMK
-> LedgerTables (LedgerState blk) KeysMK)
-> (TxOut (LedgerState blk) -> TxOut era)
-> (TxIn (LedgerState blk) -> TxIn)
-> ExtLedgerCfg (ShelleyBlock proto era)
-> BlockQuery (ShelleyBlock proto era) 'QFLookupTables result
-> ReadOnlyForker' m blk
-> m result
answerShelleyLookupQueries
(Index
(CardanoEras c)
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
-> LedgerTables
(LedgerState
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk)))
KeysMK
-> LedgerTables
(LedgerState (HardForkBlock (CardanoEras c))) KeysMK
forall (xs :: [*]) x (mk :: MapKind).
(CanMapKeysMK mk, CanMapMK mk, HasCanonicalTxIn xs,
HasHardForkTxOut xs) =>
Index xs x
-> LedgerTables (LedgerState x) mk
-> LedgerTables (LedgerState (HardForkBlock xs)) mk
injectLedgerTables Index (CardanoEras c) blk
Index
(CardanoEras c)
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
idx)
(Index (CardanoEras c) blk
-> HardForkTxOut (CardanoEras c) -> TxOut (LedgerState blk)
forall (xs :: [*]) x.
HasHardForkTxOut xs =>
Index xs x -> HardForkTxOut xs -> TxOut (LedgerState x)
forall x.
Index (CardanoEras c) x
-> HardForkTxOut (CardanoEras c) -> TxOut (LedgerState x)
ejectHardForkTxOut Index (CardanoEras c) blk
idx)
(Index (CardanoEras c) blk
-> CanonicalTxIn (CardanoEras c) -> TxIn (LedgerState blk)
forall (xs :: [*]) x.
HasCanonicalTxIn xs =>
Index xs x -> CanonicalTxIn xs -> TxIn (LedgerState x)
forall x.
Index (CardanoEras c) x
-> CanonicalTxIn (CardanoEras c) -> TxIn (LedgerState x)
ejectCanonicalTxIn Index (CardanoEras c) blk
idx)
)
answerBlockQueryHFTraverse :: forall (m :: * -> *) x result.
(All SingleEraBlock (CardanoEras c), Monad m) =>
Index (CardanoEras c) x
-> ExtLedgerCfg x
-> BlockQuery x 'QFTraverseTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
answerBlockQueryHFTraverse =
(forall blk.
IsShelleyBlock blk =>
Index (CardanoEras c) blk
-> ExtLedgerCfg blk
-> BlockQuery blk 'QFTraverseTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result)
-> Index (CardanoEras c) x
-> ExtLedgerCfg x
-> BlockQuery x 'QFTraverseTables result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
forall x (xs :: [*]) c (footprint :: QueryFootprint) result
(m :: * -> *).
(xs ~ CardanoEras c, CardanoHardForkConstraints c,
All (Compose NoThunks WrapTxOut) xs, SingI footprint) =>
(forall blk.
IsShelleyBlock blk =>
Index xs blk
-> ExtLedgerCfg blk
-> BlockQuery blk footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result)
-> Index xs x
-> ExtLedgerCfg x
-> BlockQuery x footprint result
-> ReadOnlyForker' m (HardForkBlock xs)
-> m result
answerCardanoQueryHF
( \Index (CardanoEras c) blk
idx ->
(TxOut (LedgerState (HardForkBlock (CardanoEras c)))
-> TxOut (ShelleyBlockLedgerEra blk))
-> (TxIn (LedgerState (HardForkBlock (CardanoEras c))) -> TxIn)
-> (forall result'.
BlockQuery
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
'QFTraverseTables
result'
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool)
-> ExtLedgerCfg
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
-> BlockQuery
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
'QFTraverseTables
result
-> ReadOnlyForker' m (HardForkBlock (CardanoEras c))
-> m result
forall proto era (m :: * -> *) result blk.
(ShelleyCompatible proto era, Ord (TxIn (LedgerState blk)),
Eq (TxOut (LedgerState blk)), MemPack (TxIn (LedgerState blk)),
IndexedMemPack (LedgerState blk EmptyMK) (TxOut (LedgerState blk)),
Monad m) =>
(TxOut (LedgerState blk) -> TxOut era)
-> (TxIn (LedgerState blk) -> TxIn)
-> (forall result'.
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result'
-> TxOut (LedgerState blk) -> Bool)
-> ExtLedgerCfg (ShelleyBlock proto era)
-> BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> ReadOnlyForker' m blk
-> m result
answerShelleyTraversingQueries
(Index (CardanoEras c) blk
-> HardForkTxOut (CardanoEras c) -> TxOut (LedgerState blk)
forall (xs :: [*]) x.
HasHardForkTxOut xs =>
Index xs x -> HardForkTxOut xs -> TxOut (LedgerState x)
forall x.
Index (CardanoEras c) x
-> HardForkTxOut (CardanoEras c) -> TxOut (LedgerState x)
ejectHardForkTxOut Index (CardanoEras c) blk
idx)
(Index (CardanoEras c) blk
-> CanonicalTxIn (CardanoEras c) -> TxIn (LedgerState blk)
forall (xs :: [*]) x.
HasCanonicalTxIn xs =>
Index xs x -> CanonicalTxIn xs -> TxIn (LedgerState x)
forall x.
Index (CardanoEras c) x
-> CanonicalTxIn (CardanoEras c) -> TxIn (LedgerState x)
ejectCanonicalTxIn Index (CardanoEras c) blk
idx)
(Index
(CardanoEras c)
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
-> BlockQuery
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
'QFTraverseTables
result'
-> TxOut (LedgerState (HardForkBlock (CardanoEras c)))
-> Bool
forall (xs :: [*]) x result.
BlockSupportsHFLedgerQuery xs =>
Index xs x
-> BlockQuery x 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock xs))
-> Bool
forall x result.
Index (CardanoEras c) x
-> BlockQuery x 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c)))
-> Bool
queryLedgerGetTraversingFilter Index (CardanoEras c) blk
Index
(CardanoEras c)
(ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk))
idx)
)
queryLedgerGetTraversingFilter :: forall x result.
Index (CardanoEras c) x
-> BlockQuery x 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c)))
-> Bool
queryLedgerGetTraversingFilter Index (CardanoEras c) x
idx BlockQuery x 'QFTraverseTables result
q = case Index (CardanoEras c) x
idx of
Index (CardanoEras c) x
IZ -> BlockQuery ByronBlock 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall result c.
BlockQuery ByronBlock 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
byronCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery ByronBlock 'QFTraverseTables result
q
IS Index xs' x
IZ -> BlockQuery
(ShelleyBlock (TPraos c) ShelleyEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (TPraos c) ShelleyEra) 'QFTraverseTables result
q
IS (IS Index xs' x
IZ) -> BlockQuery
(ShelleyBlock (TPraos c) AllegraEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (TPraos c) AllegraEra) 'QFTraverseTables result
q
IS (IS (IS Index xs' x
IZ)) -> BlockQuery
(ShelleyBlock (TPraos c) MaryEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (TPraos c) MaryEra) 'QFTraverseTables result
q
IS (IS (IS (IS Index xs' x
IZ))) -> BlockQuery
(ShelleyBlock (TPraos c) AlonzoEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (TPraos c) AlonzoEra) 'QFTraverseTables result
q
IS (IS (IS (IS (IS Index xs' x
IZ)))) -> BlockQuery
(ShelleyBlock (Praos c) BabbageEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (Praos c) BabbageEra) 'QFTraverseTables result
q
IS (IS (IS (IS (IS (IS Index xs' x
IZ))))) -> BlockQuery
(ShelleyBlock (Praos c) ConwayEra) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
forall proto era c result.
(CardanoHardForkConstraints c, ShelleyCompatible proto era) =>
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
shelleyCardanoFilter BlockQuery x 'QFTraverseTables result
BlockQuery
(ShelleyBlock (Praos c) ConwayEra) 'QFTraverseTables result
q
IS (IS (IS (IS (IS (IS (IS Index xs' x
idx')))))) -> case Index xs' x
idx' of {}
byronCardanoFilter ::
BlockQuery ByronBlock QFTraverseTables result ->
TxOut (LedgerState (HardForkBlock (CardanoEras c))) ->
Bool
byronCardanoFilter :: forall result c.
BlockQuery ByronBlock 'QFTraverseTables result
-> TxOut (LedgerState (HardForkBlock (CardanoEras c))) -> Bool
byronCardanoFilter = \case {}