{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Ouroboros.Consensus.HardFork.Combinator.Info (
LedgerEraInfo (..)
, SingleEraInfo (..)
) where
import Codec.Serialise (Serialise)
import Data.Text (Text)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
data SingleEraInfo blk = SingleEraInfo {
SingleEraInfo blk -> Text
singleEraName :: !Text
}
deriving stock ((forall x. SingleEraInfo blk -> Rep (SingleEraInfo blk) x)
-> (forall x. Rep (SingleEraInfo blk) x -> SingleEraInfo blk)
-> Generic (SingleEraInfo blk)
forall x. Rep (SingleEraInfo blk) x -> SingleEraInfo blk
forall x. SingleEraInfo blk -> Rep (SingleEraInfo blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (SingleEraInfo blk) x -> SingleEraInfo blk
forall blk x. SingleEraInfo blk -> Rep (SingleEraInfo blk) x
$cto :: forall blk x. Rep (SingleEraInfo blk) x -> SingleEraInfo blk
$cfrom :: forall blk x. SingleEraInfo blk -> Rep (SingleEraInfo blk) x
Generic, SingleEraInfo blk -> SingleEraInfo blk -> Bool
(SingleEraInfo blk -> SingleEraInfo blk -> Bool)
-> (SingleEraInfo blk -> SingleEraInfo blk -> Bool)
-> Eq (SingleEraInfo blk)
forall blk. SingleEraInfo blk -> SingleEraInfo blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleEraInfo blk -> SingleEraInfo blk -> Bool
$c/= :: forall blk. SingleEraInfo blk -> SingleEraInfo blk -> Bool
== :: SingleEraInfo blk -> SingleEraInfo blk -> Bool
$c== :: forall blk. SingleEraInfo blk -> SingleEraInfo blk -> Bool
Eq, Int -> SingleEraInfo blk -> ShowS
[SingleEraInfo blk] -> ShowS
SingleEraInfo blk -> String
(Int -> SingleEraInfo blk -> ShowS)
-> (SingleEraInfo blk -> String)
-> ([SingleEraInfo blk] -> ShowS)
-> Show (SingleEraInfo blk)
forall blk. Int -> SingleEraInfo blk -> ShowS
forall blk. [SingleEraInfo blk] -> ShowS
forall blk. SingleEraInfo blk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SingleEraInfo blk] -> ShowS
$cshowList :: forall blk. [SingleEraInfo blk] -> ShowS
show :: SingleEraInfo blk -> String
$cshow :: forall blk. SingleEraInfo blk -> String
showsPrec :: Int -> SingleEraInfo blk -> ShowS
$cshowsPrec :: forall blk. Int -> SingleEraInfo blk -> ShowS
Show)
deriving anyclass (Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
Proxy (SingleEraInfo blk) -> String
(Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo))
-> (Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo))
-> (Proxy (SingleEraInfo blk) -> String)
-> NoThunks (SingleEraInfo blk)
forall blk. Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
forall blk. Proxy (SingleEraInfo blk) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SingleEraInfo blk) -> String
$cshowTypeOf :: forall blk. Proxy (SingleEraInfo blk) -> String
wNoThunks :: Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall blk. Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall blk. Context -> SingleEraInfo blk -> IO (Maybe ThunkInfo)
NoThunks, [SingleEraInfo blk] -> Encoding
SingleEraInfo blk -> Encoding
(SingleEraInfo blk -> Encoding)
-> (forall s. Decoder s (SingleEraInfo blk))
-> ([SingleEraInfo blk] -> Encoding)
-> (forall s. Decoder s [SingleEraInfo blk])
-> Serialise (SingleEraInfo blk)
forall s. Decoder s [SingleEraInfo blk]
forall s. Decoder s (SingleEraInfo blk)
forall blk. [SingleEraInfo blk] -> Encoding
forall blk. SingleEraInfo blk -> Encoding
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
forall blk s. Decoder s [SingleEraInfo blk]
forall blk s. Decoder s (SingleEraInfo blk)
decodeList :: Decoder s [SingleEraInfo blk]
$cdecodeList :: forall blk s. Decoder s [SingleEraInfo blk]
encodeList :: [SingleEraInfo blk] -> Encoding
$cencodeList :: forall blk. [SingleEraInfo blk] -> Encoding
decode :: Decoder s (SingleEraInfo blk)
$cdecode :: forall blk s. Decoder s (SingleEraInfo blk)
encode :: SingleEraInfo blk -> Encoding
$cencode :: forall blk. SingleEraInfo blk -> Encoding
Serialise)
newtype LedgerEraInfo blk = LedgerEraInfo {
LedgerEraInfo blk -> SingleEraInfo blk
getLedgerEraInfo :: SingleEraInfo blk
}
deriving stock (LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
(LedgerEraInfo blk -> LedgerEraInfo blk -> Bool)
-> (LedgerEraInfo blk -> LedgerEraInfo blk -> Bool)
-> Eq (LedgerEraInfo blk)
forall blk. LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
$c/= :: forall blk. LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
== :: LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
$c== :: forall blk. LedgerEraInfo blk -> LedgerEraInfo blk -> Bool
Eq, Int -> LedgerEraInfo blk -> ShowS
[LedgerEraInfo blk] -> ShowS
LedgerEraInfo blk -> String
(Int -> LedgerEraInfo blk -> ShowS)
-> (LedgerEraInfo blk -> String)
-> ([LedgerEraInfo blk] -> ShowS)
-> Show (LedgerEraInfo blk)
forall blk. Int -> LedgerEraInfo blk -> ShowS
forall blk. [LedgerEraInfo blk] -> ShowS
forall blk. LedgerEraInfo blk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LedgerEraInfo blk] -> ShowS
$cshowList :: forall blk. [LedgerEraInfo blk] -> ShowS
show :: LedgerEraInfo blk -> String
$cshow :: forall blk. LedgerEraInfo blk -> String
showsPrec :: Int -> LedgerEraInfo blk -> ShowS
$cshowsPrec :: forall blk. Int -> LedgerEraInfo blk -> ShowS
Show)
deriving newtype (Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
Proxy (LedgerEraInfo blk) -> String
(Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo))
-> (Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo))
-> (Proxy (LedgerEraInfo blk) -> String)
-> NoThunks (LedgerEraInfo blk)
forall blk. Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
forall blk. Proxy (LedgerEraInfo blk) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (LedgerEraInfo blk) -> String
$cshowTypeOf :: forall blk. Proxy (LedgerEraInfo blk) -> String
wNoThunks :: Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall blk. Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall blk. Context -> LedgerEraInfo blk -> IO (Maybe ThunkInfo)
NoThunks, Decoder s (LedgerEraInfo blk)
Decoder s [LedgerEraInfo blk]
[LedgerEraInfo blk] -> Encoding
LedgerEraInfo blk -> Encoding
(LedgerEraInfo blk -> Encoding)
-> (forall s. Decoder s (LedgerEraInfo blk))
-> ([LedgerEraInfo blk] -> Encoding)
-> (forall s. Decoder s [LedgerEraInfo blk])
-> Serialise (LedgerEraInfo blk)
forall s. Decoder s [LedgerEraInfo blk]
forall s. Decoder s (LedgerEraInfo blk)
forall blk. [LedgerEraInfo blk] -> Encoding
forall blk. LedgerEraInfo blk -> Encoding
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
forall blk s. Decoder s [LedgerEraInfo blk]
forall blk s. Decoder s (LedgerEraInfo blk)
decodeList :: Decoder s [LedgerEraInfo blk]
$cdecodeList :: forall blk s. Decoder s [LedgerEraInfo blk]
encodeList :: [LedgerEraInfo blk] -> Encoding
$cencodeList :: forall blk. [LedgerEraInfo blk] -> Encoding
decode :: Decoder s (LedgerEraInfo blk)
$cdecode :: forall blk s. Decoder s (LedgerEraInfo blk)
encode :: LedgerEraInfo blk -> Encoding
$cencode :: forall blk. LedgerEraInfo blk -> Encoding
Serialise)