{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Ledger.Dijkstra.Genesis ( DijkstraGenesis (..), ) where import Cardano.Ledger.BaseTypes (ToKeyValuePairs (..)) import Cardano.Ledger.Binary ( DecCBOR (..), EncCBOR (..), FromCBOR (..), ToCBOR (..), ) import Cardano.Ledger.Binary.Coders import Cardano.Ledger.Core import Cardano.Ledger.Dijkstra.Era (DijkstraEra) import Cardano.Ledger.Dijkstra.PParams (UpgradeDijkstraPParams) import Cardano.Ledger.Genesis (EraGenesis (..)) import Control.DeepSeq (NFData) import Data.Aeson (FromJSON (..), ToJSON) import Data.Functor.Identity (Identity) import GHC.Generics import NoThunks.Class (NoThunks) newtype DijkstraGenesis = DijkstraGenesis { DijkstraGenesis -> UpgradeDijkstraPParams Identity DijkstraEra dgUpgradePParams :: UpgradeDijkstraPParams Identity DijkstraEra } deriving (DijkstraGenesis -> DijkstraGenesis -> Bool (DijkstraGenesis -> DijkstraGenesis -> Bool) -> (DijkstraGenesis -> DijkstraGenesis -> Bool) -> Eq DijkstraGenesis forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: DijkstraGenesis -> DijkstraGenesis -> Bool == :: DijkstraGenesis -> DijkstraGenesis -> Bool $c/= :: DijkstraGenesis -> DijkstraGenesis -> Bool /= :: DijkstraGenesis -> DijkstraGenesis -> Bool Eq, Int -> DijkstraGenesis -> ShowS [DijkstraGenesis] -> ShowS DijkstraGenesis -> String (Int -> DijkstraGenesis -> ShowS) -> (DijkstraGenesis -> String) -> ([DijkstraGenesis] -> ShowS) -> Show DijkstraGenesis forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> DijkstraGenesis -> ShowS showsPrec :: Int -> DijkstraGenesis -> ShowS $cshow :: DijkstraGenesis -> String show :: DijkstraGenesis -> String $cshowList :: [DijkstraGenesis] -> ShowS showList :: [DijkstraGenesis] -> ShowS Show, (forall x. DijkstraGenesis -> Rep DijkstraGenesis x) -> (forall x. Rep DijkstraGenesis x -> DijkstraGenesis) -> Generic DijkstraGenesis forall x. Rep DijkstraGenesis x -> DijkstraGenesis forall x. DijkstraGenesis -> Rep DijkstraGenesis x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. DijkstraGenesis -> Rep DijkstraGenesis x from :: forall x. DijkstraGenesis -> Rep DijkstraGenesis x $cto :: forall x. Rep DijkstraGenesis x -> DijkstraGenesis to :: forall x. Rep DijkstraGenesis x -> DijkstraGenesis Generic, Context -> DijkstraGenesis -> IO (Maybe ThunkInfo) Proxy DijkstraGenesis -> String (Context -> DijkstraGenesis -> IO (Maybe ThunkInfo)) -> (Context -> DijkstraGenesis -> IO (Maybe ThunkInfo)) -> (Proxy DijkstraGenesis -> String) -> NoThunks DijkstraGenesis forall a. (Context -> a -> IO (Maybe ThunkInfo)) -> (Context -> a -> IO (Maybe ThunkInfo)) -> (Proxy a -> String) -> NoThunks a $cnoThunks :: Context -> DijkstraGenesis -> IO (Maybe ThunkInfo) noThunks :: Context -> DijkstraGenesis -> IO (Maybe ThunkInfo) $cwNoThunks :: Context -> DijkstraGenesis -> IO (Maybe ThunkInfo) wNoThunks :: Context -> DijkstraGenesis -> IO (Maybe ThunkInfo) $cshowTypeOf :: Proxy DijkstraGenesis -> String showTypeOf :: Proxy DijkstraGenesis -> String NoThunks, [DijkstraGenesis] -> Value [DijkstraGenesis] -> Encoding DijkstraGenesis -> Bool DijkstraGenesis -> Value DijkstraGenesis -> Encoding (DijkstraGenesis -> Value) -> (DijkstraGenesis -> Encoding) -> ([DijkstraGenesis] -> Value) -> ([DijkstraGenesis] -> Encoding) -> (DijkstraGenesis -> Bool) -> ToJSON DijkstraGenesis forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> (a -> Bool) -> ToJSON a $ctoJSON :: DijkstraGenesis -> Value toJSON :: DijkstraGenesis -> Value $ctoEncoding :: DijkstraGenesis -> Encoding toEncoding :: DijkstraGenesis -> Encoding $ctoJSONList :: [DijkstraGenesis] -> Value toJSONList :: [DijkstraGenesis] -> Value $ctoEncodingList :: [DijkstraGenesis] -> Encoding toEncodingList :: [DijkstraGenesis] -> Encoding $comitField :: DijkstraGenesis -> Bool omitField :: DijkstraGenesis -> Bool ToJSON, Maybe DijkstraGenesis Value -> Parser [DijkstraGenesis] Value -> Parser DijkstraGenesis (Value -> Parser DijkstraGenesis) -> (Value -> Parser [DijkstraGenesis]) -> Maybe DijkstraGenesis -> FromJSON DijkstraGenesis forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe a -> FromJSON a $cparseJSON :: Value -> Parser DijkstraGenesis parseJSON :: Value -> Parser DijkstraGenesis $cparseJSONList :: Value -> Parser [DijkstraGenesis] parseJSONList :: Value -> Parser [DijkstraGenesis] $comittedField :: Maybe DijkstraGenesis omittedField :: Maybe DijkstraGenesis FromJSON, (forall e kv. KeyValue e kv => DijkstraGenesis -> [kv]) -> ToKeyValuePairs DijkstraGenesis forall a. (forall e kv. KeyValue e kv => a -> [kv]) -> ToKeyValuePairs a forall e kv. KeyValue e kv => DijkstraGenesis -> [kv] $ctoKeyValuePairs :: forall e kv. KeyValue e kv => DijkstraGenesis -> [kv] toKeyValuePairs :: forall e kv. KeyValue e kv => DijkstraGenesis -> [kv] ToKeyValuePairs, DijkstraGenesis -> () (DijkstraGenesis -> ()) -> NFData DijkstraGenesis forall a. (a -> ()) -> NFData a $crnf :: DijkstraGenesis -> () rnf :: DijkstraGenesis -> () NFData) instance EraGenesis DijkstraEra where type Genesis DijkstraEra = DijkstraGenesis instance FromCBOR DijkstraGenesis where fromCBOR :: forall s. Decoder s DijkstraGenesis fromCBOR = forall era t s. Era era => Decoder s t -> Decoder s t eraDecoder @DijkstraEra (Decoder s DijkstraGenesis -> Decoder s DijkstraGenesis) -> Decoder s DijkstraGenesis -> Decoder s DijkstraGenesis forall a b. (a -> b) -> a -> b $ Decode (Closed Dense) DijkstraGenesis -> Decoder s DijkstraGenesis forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t decode (Decode (Closed Dense) DijkstraGenesis -> Decoder s DijkstraGenesis) -> Decode (Closed Dense) DijkstraGenesis -> Decoder s DijkstraGenesis forall a b. (a -> b) -> a -> b $ (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) -> Decode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) forall t. t -> Decode (Closed Dense) t RecD UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis DijkstraGenesis Decode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) -> Decode (Closed (ZonkAny 0)) (UpgradeDijkstraPParams Identity DijkstraEra) -> Decode (Closed Dense) DijkstraGenesis forall a (w1 :: Wrapped) t (w :: Density). Typeable a => Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t <! Decode (Closed (ZonkAny 0)) (UpgradeDijkstraPParams Identity DijkstraEra) forall t (w :: Wrapped). DecCBOR t => Decode w t From instance ToCBOR DijkstraGenesis where toCBOR :: DijkstraGenesis -> Encoding toCBOR dg :: DijkstraGenesis dg@(DijkstraGenesis UpgradeDijkstraPParams Identity DijkstraEra _) = let DijkstraGenesis {UpgradeDijkstraPParams Identity DijkstraEra dgUpgradePParams :: DijkstraGenesis -> UpgradeDijkstraPParams Identity DijkstraEra dgUpgradePParams :: UpgradeDijkstraPParams Identity DijkstraEra ..} = DijkstraGenesis dg in forall era t. (Era era, EncCBOR t) => t -> Encoding toEraCBOR @DijkstraEra (Encoding -> Encoding) -> (Encode (Closed Dense) DijkstraGenesis -> Encoding) -> Encode (Closed Dense) DijkstraGenesis -> Encoding forall b c a. (b -> c) -> (a -> b) -> a -> c . Encode (Closed Dense) DijkstraGenesis -> Encoding forall (w :: Wrapped) t. Encode w t -> Encoding encode (Encode (Closed Dense) DijkstraGenesis -> Encoding) -> Encode (Closed Dense) DijkstraGenesis -> Encoding forall a b. (a -> b) -> a -> b $ (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) -> Encode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) forall t. t -> Encode (Closed Dense) t Rec UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis DijkstraGenesis Encode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra -> DijkstraGenesis) -> Encode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra) -> Encode (Closed Dense) DijkstraGenesis forall (w :: Wrapped) a t (r :: Density). Encode w (a -> t) -> Encode (Closed r) a -> Encode w t !> UpgradeDijkstraPParams Identity DijkstraEra -> Encode (Closed Dense) (UpgradeDijkstraPParams Identity DijkstraEra) forall t. EncCBOR t => t -> Encode (Closed Dense) t To UpgradeDijkstraPParams Identity DijkstraEra dgUpgradePParams instance DecCBOR DijkstraGenesis instance EncCBOR DijkstraGenesis