{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Ouroboros.Consensus.BlockchainTime.API (
BlockchainTime (..)
, CurrentSlot (..)
, knownSlotWatcher
) where
import GHC.Generics (Generic)
import NoThunks.Class (OnlyCheckWhnfNamed (..))
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Util.IOLike
import Ouroboros.Consensus.Util.STM (Watcher (..))
data BlockchainTime m = BlockchainTime {
forall (m :: * -> *). BlockchainTime m -> STM m CurrentSlot
getCurrentSlot :: STM m CurrentSlot
}
deriving Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
Proxy (BlockchainTime m) -> String
(Context -> BlockchainTime m -> IO (Maybe ThunkInfo))
-> (Context -> BlockchainTime m -> IO (Maybe ThunkInfo))
-> (Proxy (BlockchainTime m) -> String)
-> NoThunks (BlockchainTime m)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *).
Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
forall (m :: * -> *). Proxy (BlockchainTime m) -> String
$cnoThunks :: forall (m :: * -> *).
Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *).
Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> BlockchainTime m -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall (m :: * -> *). Proxy (BlockchainTime m) -> String
showTypeOf :: Proxy (BlockchainTime m) -> String
NoThunks
via OnlyCheckWhnfNamed "BlockchainTime" (BlockchainTime m)
data CurrentSlot =
CurrentSlot !SlotNo
| CurrentSlotUnknown
deriving stock ((forall x. CurrentSlot -> Rep CurrentSlot x)
-> (forall x. Rep CurrentSlot x -> CurrentSlot)
-> Generic CurrentSlot
forall x. Rep CurrentSlot x -> CurrentSlot
forall x. CurrentSlot -> Rep CurrentSlot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CurrentSlot -> Rep CurrentSlot x
from :: forall x. CurrentSlot -> Rep CurrentSlot x
$cto :: forall x. Rep CurrentSlot x -> CurrentSlot
to :: forall x. Rep CurrentSlot x -> CurrentSlot
Generic, Int -> CurrentSlot -> ShowS
[CurrentSlot] -> ShowS
CurrentSlot -> String
(Int -> CurrentSlot -> ShowS)
-> (CurrentSlot -> String)
-> ([CurrentSlot] -> ShowS)
-> Show CurrentSlot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CurrentSlot -> ShowS
showsPrec :: Int -> CurrentSlot -> ShowS
$cshow :: CurrentSlot -> String
show :: CurrentSlot -> String
$cshowList :: [CurrentSlot] -> ShowS
showList :: [CurrentSlot] -> ShowS
Show)
deriving anyclass (Context -> CurrentSlot -> IO (Maybe ThunkInfo)
Proxy CurrentSlot -> String
(Context -> CurrentSlot -> IO (Maybe ThunkInfo))
-> (Context -> CurrentSlot -> IO (Maybe ThunkInfo))
-> (Proxy CurrentSlot -> String)
-> NoThunks CurrentSlot
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> CurrentSlot -> IO (Maybe ThunkInfo)
noThunks :: Context -> CurrentSlot -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CurrentSlot -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> CurrentSlot -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy CurrentSlot -> String
showTypeOf :: Proxy CurrentSlot -> String
NoThunks)
knownSlotWatcher :: forall m. IOLike m
=> BlockchainTime m
-> (SlotNo -> m ())
-> Watcher m SlotNo SlotNo
knownSlotWatcher :: forall (m :: * -> *).
IOLike m =>
BlockchainTime m -> (SlotNo -> m ()) -> Watcher m SlotNo SlotNo
knownSlotWatcher BlockchainTime m
btime SlotNo -> m ()
notify =
Watcher {
wFingerprint :: SlotNo -> SlotNo
wFingerprint = SlotNo -> SlotNo
forall a. a -> a
id
, wInitial :: Maybe SlotNo
wInitial = Maybe SlotNo
forall a. Maybe a
Nothing
, wNotify :: SlotNo -> m ()
wNotify = SlotNo -> m ()
notify
, wReader :: STM m SlotNo
wReader = STM m SlotNo
getCurrentSlot'
}
where
getCurrentSlot' :: STM m SlotNo
getCurrentSlot' :: STM m SlotNo
getCurrentSlot' = do
CurrentSlot
mSlot <- BlockchainTime m -> STM m CurrentSlot
forall (m :: * -> *). BlockchainTime m -> STM m CurrentSlot
getCurrentSlot BlockchainTime m
btime
case CurrentSlot
mSlot of
CurrentSlot
CurrentSlotUnknown -> STM m SlotNo
forall a. STM m a
forall (m :: * -> *) a. MonadSTM m => STM m a
retry
CurrentSlot SlotNo
s -> SlotNo -> STM m SlotNo
forall a. a -> STM m a
forall (m :: * -> *) a. Monad m => a -> m a
return SlotNo
s