{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Ouroboros.Consensus.HardFork.Combinator.Compat (
HardForkCompatQuery (..)
, compatGetEraStart
, compatGetInterpreter
, compatIfCurrent
, forwardCompatQuery
, singleEraCompatQuery
) where
import Data.Kind (Type)
import Data.SOP.BasicFunctors
import Data.SOP.NonEmpty
import Data.SOP.Strict
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.BlockchainTime
import Ouroboros.Consensus.HardFork.Abstract
import Ouroboros.Consensus.HardFork.Combinator.Abstract.SingleEraBlock
import Ouroboros.Consensus.HardFork.Combinator.Basics
import Ouroboros.Consensus.HardFork.Combinator.Ledger.Query
import qualified Ouroboros.Consensus.HardFork.History.Qry as Qry
import Ouroboros.Consensus.HardFork.History.Summary (Bound, Summary,
initBound, neverForksSummary)
data HardForkCompatQuery blk :: Type -> Type where
CompatIfCurrent ::
BlockQuery blk result
-> HardForkCompatQuery blk result
CompatAnytime ::
QueryAnytime result
-> EraIndex (HardForkIndices blk)
-> HardForkCompatQuery blk result
CompatHardFork ::
QueryHardFork (HardForkIndices blk) result
-> HardForkCompatQuery blk result
compatIfCurrent ::
BlockQuery blk result
-> HardForkCompatQuery blk result
compatIfCurrent :: forall blk result.
BlockQuery blk result -> HardForkCompatQuery blk result
compatIfCurrent = BlockQuery blk result -> HardForkCompatQuery blk result
forall blk result.
BlockQuery blk result -> HardForkCompatQuery blk result
CompatIfCurrent
compatGetEraStart ::
EraIndex (HardForkIndices blk)
-> HardForkCompatQuery blk (Maybe Bound)
compatGetEraStart :: forall blk.
EraIndex (HardForkIndices blk)
-> HardForkCompatQuery blk (Maybe Bound)
compatGetEraStart = QueryAnytime (Maybe Bound)
-> EraIndex (HardForkIndices blk)
-> HardForkCompatQuery blk (Maybe Bound)
forall result blk.
QueryAnytime result
-> EraIndex (HardForkIndices blk) -> HardForkCompatQuery blk result
CompatAnytime QueryAnytime (Maybe Bound)
GetEraStart
compatGetInterpreter ::
HardForkCompatQuery blk (Qry.Interpreter (HardForkIndices blk))
compatGetInterpreter :: forall blk.
HardForkCompatQuery blk (Interpreter (HardForkIndices blk))
compatGetInterpreter = QueryHardFork
(HardForkIndices blk) (Interpreter (HardForkIndices blk))
-> HardForkCompatQuery blk (Interpreter (HardForkIndices blk))
forall blk result.
QueryHardFork (HardForkIndices blk) result
-> HardForkCompatQuery blk result
CompatHardFork QueryHardFork
(HardForkIndices blk) (Interpreter (HardForkIndices blk))
forall (xs :: [*]). QueryHardFork xs (Interpreter xs)
GetInterpreter
forwardCompatQuery ::
forall m x xs. IsNonEmpty xs
=> (forall result. BlockQuery (HardForkBlock (x ': xs)) result -> m result)
-> (forall result. HardForkCompatQuery (HardForkBlock (x ': xs)) result -> m result)
forwardCompatQuery :: forall (m :: * -> *) x (xs :: [*]).
IsNonEmpty xs =>
(forall result.
BlockQuery (HardForkBlock (x : xs)) result -> m result)
-> forall result.
HardForkCompatQuery (HardForkBlock (x : xs)) result -> m result
forwardCompatQuery forall result.
BlockQuery (HardForkBlock (x : xs)) result -> m result
f = HardForkCompatQuery (HardForkBlock (x : xs)) result -> m result
forall result.
HardForkCompatQuery (HardForkBlock (x : xs)) result -> m result
go
where
go :: HardForkCompatQuery (HardForkBlock (x ': xs)) result -> m result
go :: forall result.
HardForkCompatQuery (HardForkBlock (x : xs)) result -> m result
go (CompatIfCurrent BlockQuery (HardForkBlock (x : xs)) result
qry) = BlockQuery (HardForkBlock (x : xs)) result -> m result
forall result.
BlockQuery (HardForkBlock (x : xs)) result -> m result
f BlockQuery (HardForkBlock (x : xs)) result
qry
go (CompatAnytime QueryAnytime result
qry EraIndex (HardForkIndices (HardForkBlock (x : xs)))
ix) = BlockQuery (HardForkBlock (x : xs)) result -> m result
forall result.
BlockQuery (HardForkBlock (x : xs)) result -> m result
f (QueryAnytime result
-> EraIndex (x : xs) -> BlockQuery (HardForkBlock (x : xs)) result
forall (xs1 :: [*]) a x.
IsNonEmpty xs1 =>
QueryAnytime a
-> EraIndex (x : xs1) -> BlockQuery (HardForkBlock (x : xs1)) a
QueryAnytime QueryAnytime result
qry EraIndex (x : xs)
EraIndex (HardForkIndices (HardForkBlock (x : xs)))
ix)
go (CompatHardFork QueryHardFork (HardForkIndices (HardForkBlock (x : xs))) result
qry) = BlockQuery (HardForkBlock (x : xs)) result -> m result
forall result.
BlockQuery (HardForkBlock (x : xs)) result -> m result
f (QueryHardFork (x : xs) result
-> BlockQuery (HardForkBlock (x : xs)) result
forall (xs1 :: [*]) x a.
IsNonEmpty xs1 =>
QueryHardFork (x : xs1) a -> BlockQuery (HardForkBlock (x : xs1)) a
QueryHardFork QueryHardFork (x : xs) result
QueryHardFork (HardForkIndices (HardForkBlock (x : xs))) result
qry)
singleEraCompatQuery ::
forall m blk era. (Monad m, HardForkIndices blk ~ '[era])
=> EpochSize
-> SlotLength
-> GenesisWindow
-> (forall result. BlockQuery blk result -> m result)
-> (forall result. HardForkCompatQuery blk result -> m result)
singleEraCompatQuery :: forall (m :: * -> *) blk era.
(Monad m, HardForkIndices blk ~ '[era]) =>
EpochSize
-> SlotLength
-> GenesisWindow
-> (forall result. BlockQuery blk result -> m result)
-> forall result. HardForkCompatQuery blk result -> m result
singleEraCompatQuery EpochSize
epochSize SlotLength
slotLen GenesisWindow
genesisWindow forall result. BlockQuery blk result -> m result
f = HardForkCompatQuery blk result -> m result
forall result. HardForkCompatQuery blk result -> m result
go
where
go :: HardForkCompatQuery blk result -> m result
go :: forall result. HardForkCompatQuery blk result -> m result
go (CompatIfCurrent BlockQuery blk result
qry) = BlockQuery blk result -> m result
forall result. BlockQuery blk result -> m result
f BlockQuery blk result
qry
go (CompatAnytime QueryAnytime result
qry EraIndex (HardForkIndices blk)
ix) = m result -> () -> m result
forall a b. a -> b -> a
const (QueryAnytime result -> m result
forall result. QueryAnytime result -> m result
goAnytime QueryAnytime result
qry) (EraIndex '[era] -> ()
trivialIndex EraIndex '[era]
EraIndex (HardForkIndices blk)
ix)
go (CompatHardFork QueryHardFork (HardForkIndices blk) result
qry) = QueryHardFork '[era] result -> m result
forall result. QueryHardFork '[era] result -> m result
goHardFork QueryHardFork '[era] result
QueryHardFork (HardForkIndices blk) result
qry
goAnytime :: QueryAnytime result -> m result
goAnytime :: forall result. QueryAnytime result -> m result
goAnytime QueryAnytime result
GetEraStart = result -> m result
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (result -> m result) -> result -> m result
forall a b. (a -> b) -> a -> b
$ Bound -> Maybe Bound
forall a. a -> Maybe a
Just Bound
initBound
goHardFork :: QueryHardFork '[era] result -> m result
goHardFork :: forall result. QueryHardFork '[era] result -> m result
goHardFork QueryHardFork '[era] result
GetInterpreter = result -> m result
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (result -> m result) -> result -> m result
forall a b. (a -> b) -> a -> b
$ Summary '[era] -> Interpreter '[era]
forall (xs :: [*]). Summary xs -> Interpreter xs
Qry.mkInterpreter Summary '[era]
summary
goHardFork QueryHardFork '[era] result
GetCurrentEra = result -> m result
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (result -> m result) -> result -> m result
forall a b. (a -> b) -> a -> b
$ result
EraIndex '[era]
forall x (xs :: [*]). EraIndex (x : xs)
eraIndexZero
summary :: Summary '[era]
summary :: Summary '[era]
summary = EpochSize -> SlotLength -> GenesisWindow -> Summary '[era]
forall x. EpochSize -> SlotLength -> GenesisWindow -> Summary '[x]
neverForksSummary EpochSize
epochSize SlotLength
slotLen GenesisWindow
genesisWindow
trivialIndex :: EraIndex '[era] -> ()
trivialIndex :: EraIndex '[era] -> ()
trivialIndex (EraIndex (Z (K ()))) = ()