{-# LANGUAGE TypeFamilyDependencies #-}
module Hydra.Chain.ChainState where
import Hydra.Prelude
import Hydra.Tx (IsTx (..))
newtype ChainSlot = ChainSlot Natural
deriving stock (Eq ChainSlot
Eq ChainSlot =>
(ChainSlot -> ChainSlot -> Ordering)
-> (ChainSlot -> ChainSlot -> Bool)
-> (ChainSlot -> ChainSlot -> Bool)
-> (ChainSlot -> ChainSlot -> Bool)
-> (ChainSlot -> ChainSlot -> Bool)
-> (ChainSlot -> ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot -> ChainSlot)
-> Ord ChainSlot
ChainSlot -> ChainSlot -> Bool
ChainSlot -> ChainSlot -> Ordering
ChainSlot -> ChainSlot -> ChainSlot
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChainSlot -> ChainSlot -> Ordering
compare :: ChainSlot -> ChainSlot -> Ordering
$c< :: ChainSlot -> ChainSlot -> Bool
< :: ChainSlot -> ChainSlot -> Bool
$c<= :: ChainSlot -> ChainSlot -> Bool
<= :: ChainSlot -> ChainSlot -> Bool
$c> :: ChainSlot -> ChainSlot -> Bool
> :: ChainSlot -> ChainSlot -> Bool
$c>= :: ChainSlot -> ChainSlot -> Bool
>= :: ChainSlot -> ChainSlot -> Bool
$cmax :: ChainSlot -> ChainSlot -> ChainSlot
max :: ChainSlot -> ChainSlot -> ChainSlot
$cmin :: ChainSlot -> ChainSlot -> ChainSlot
min :: ChainSlot -> ChainSlot -> ChainSlot
Ord, ChainSlot -> ChainSlot -> Bool
(ChainSlot -> ChainSlot -> Bool)
-> (ChainSlot -> ChainSlot -> Bool) -> Eq ChainSlot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChainSlot -> ChainSlot -> Bool
== :: ChainSlot -> ChainSlot -> Bool
$c/= :: ChainSlot -> ChainSlot -> Bool
/= :: ChainSlot -> ChainSlot -> Bool
Eq, Int -> ChainSlot -> ShowS
[ChainSlot] -> ShowS
ChainSlot -> String
(Int -> ChainSlot -> ShowS)
-> (ChainSlot -> String)
-> ([ChainSlot] -> ShowS)
-> Show ChainSlot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChainSlot -> ShowS
showsPrec :: Int -> ChainSlot -> ShowS
$cshow :: ChainSlot -> String
show :: ChainSlot -> String
$cshowList :: [ChainSlot] -> ShowS
showList :: [ChainSlot] -> ShowS
Show, (forall x. ChainSlot -> Rep ChainSlot x)
-> (forall x. Rep ChainSlot x -> ChainSlot) -> Generic ChainSlot
forall x. Rep ChainSlot x -> ChainSlot
forall x. ChainSlot -> Rep ChainSlot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChainSlot -> Rep ChainSlot x
from :: forall x. ChainSlot -> Rep ChainSlot x
$cto :: forall x. Rep ChainSlot x -> ChainSlot
to :: forall x. Rep ChainSlot x -> ChainSlot
Generic)
deriving newtype (Integer -> ChainSlot
ChainSlot -> ChainSlot
ChainSlot -> ChainSlot -> ChainSlot
(ChainSlot -> ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot)
-> (ChainSlot -> ChainSlot)
-> (Integer -> ChainSlot)
-> Num ChainSlot
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ChainSlot -> ChainSlot -> ChainSlot
+ :: ChainSlot -> ChainSlot -> ChainSlot
$c- :: ChainSlot -> ChainSlot -> ChainSlot
- :: ChainSlot -> ChainSlot -> ChainSlot
$c* :: ChainSlot -> ChainSlot -> ChainSlot
* :: ChainSlot -> ChainSlot -> ChainSlot
$cnegate :: ChainSlot -> ChainSlot
negate :: ChainSlot -> ChainSlot
$cabs :: ChainSlot -> ChainSlot
abs :: ChainSlot -> ChainSlot
$csignum :: ChainSlot -> ChainSlot
signum :: ChainSlot -> ChainSlot
$cfromInteger :: Integer -> ChainSlot
fromInteger :: Integer -> ChainSlot
Num, [ChainSlot] -> Value
[ChainSlot] -> Encoding
ChainSlot -> Bool
ChainSlot -> Value
ChainSlot -> Encoding
(ChainSlot -> Value)
-> (ChainSlot -> Encoding)
-> ([ChainSlot] -> Value)
-> ([ChainSlot] -> Encoding)
-> (ChainSlot -> Bool)
-> ToJSON ChainSlot
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ChainSlot -> Value
toJSON :: ChainSlot -> Value
$ctoEncoding :: ChainSlot -> Encoding
toEncoding :: ChainSlot -> Encoding
$ctoJSONList :: [ChainSlot] -> Value
toJSONList :: [ChainSlot] -> Value
$ctoEncodingList :: [ChainSlot] -> Encoding
toEncodingList :: [ChainSlot] -> Encoding
$comitField :: ChainSlot -> Bool
omitField :: ChainSlot -> Bool
ToJSON, Maybe ChainSlot
Value -> Parser [ChainSlot]
Value -> Parser ChainSlot
(Value -> Parser ChainSlot)
-> (Value -> Parser [ChainSlot])
-> Maybe ChainSlot
-> FromJSON ChainSlot
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ChainSlot
parseJSON :: Value -> Parser ChainSlot
$cparseJSONList :: Value -> Parser [ChainSlot]
parseJSONList :: Value -> Parser [ChainSlot]
$comittedField :: Maybe ChainSlot
omittedField :: Maybe ChainSlot
FromJSON, Gen ChainSlot
Gen ChainSlot -> (ChainSlot -> [ChainSlot]) -> Arbitrary ChainSlot
ChainSlot -> [ChainSlot]
forall a. Gen a -> (a -> [a]) -> Arbitrary a
$carbitrary :: Gen ChainSlot
arbitrary :: Gen ChainSlot
$cshrink :: ChainSlot -> [ChainSlot]
shrink :: ChainSlot -> [ChainSlot]
Arbitrary)
class
( IsTx tx
, Eq (ChainStateType tx)
, Show (ChainStateType tx)
, FromJSON (ChainStateType tx)
, ToJSON (ChainStateType tx)
, Arbitrary (ChainStateType tx)
) =>
IsChainState tx
where
type ChainStateType tx = c | c -> tx
chainStateSlot :: ChainStateType tx -> ChainSlot