{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-missed-specialisations #-}
module Cardano.Chain.Genesis.Delegation (
GenesisDelegation (..),
GenesisDelegationError,
mkGenesisDelegation,
)
where
import Cardano.Chain.Common (KeyHash, hashKey)
import Cardano.Chain.Delegation.Certificate (
ACertificate (delegateVK, issuerVK),
Certificate,
)
import Cardano.Ledger.Binary
import Cardano.Prelude
import Data.List (nub)
import qualified Data.Map.Strict as M
import Formatting (bprint, build, formatToString)
import qualified Formatting.Buildable as B
import NoThunks.Class (NoThunks (..))
import Text.JSON.Canonical (FromJSON (..), ReportSchemaErrors (..), ToJSON (..))
newtype GenesisDelegation = UnsafeGenesisDelegation
{ GenesisDelegation -> Map KeyHash Certificate
unGenesisDelegation :: Map KeyHash Certificate
}
deriving (Int -> GenesisDelegation -> ShowS
[GenesisDelegation] -> ShowS
GenesisDelegation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenesisDelegation] -> ShowS
$cshowList :: [GenesisDelegation] -> ShowS
show :: GenesisDelegation -> String
$cshow :: GenesisDelegation -> String
showsPrec :: Int -> GenesisDelegation -> ShowS
$cshowsPrec :: Int -> GenesisDelegation -> ShowS
Show, GenesisDelegation -> GenesisDelegation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenesisDelegation -> GenesisDelegation -> Bool
$c/= :: GenesisDelegation -> GenesisDelegation -> Bool
== :: GenesisDelegation -> GenesisDelegation -> Bool
$c== :: GenesisDelegation -> GenesisDelegation -> Bool
Eq, Context -> GenesisDelegation -> IO (Maybe ThunkInfo)
Proxy GenesisDelegation -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy GenesisDelegation -> String
$cshowTypeOf :: Proxy GenesisDelegation -> String
wNoThunks :: Context -> GenesisDelegation -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> GenesisDelegation -> IO (Maybe ThunkInfo)
noThunks :: Context -> GenesisDelegation -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> GenesisDelegation -> IO (Maybe ThunkInfo)
NoThunks)
instance Monad m => ToJSON m GenesisDelegation where
toJSON :: GenesisDelegation -> m JSValue
toJSON = forall (m :: * -> *) a. ToJSON m a => a -> m JSValue
toJSON forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. GenesisDelegation -> Map KeyHash Certificate
unGenesisDelegation
instance MonadError SchemaError m => FromJSON m GenesisDelegation where
fromJSON :: JSValue -> m GenesisDelegation
fromJSON JSValue
val = do
Map KeyHash Certificate
certs <- forall (m :: * -> *) a. FromJSON m a => JSValue -> m a
fromJSON JSValue
val
case forall (m :: * -> *).
MonadError GenesisDelegationError m =>
Map KeyHash Certificate -> m GenesisDelegation
recreateGenesisDelegation Map KeyHash Certificate
certs of
Left GenesisDelegationError
err ->
forall (m :: * -> *) a.
ReportSchemaErrors m =>
String -> Maybe String -> m a
expected
String
"GenesisDelegation"
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String
"Error: " forall a. Semigroup a => a -> a -> a
<> forall a. Format String a -> a
formatToString forall a r. Buildable a => Format r (a -> r)
build GenesisDelegationError
err)
Right GenesisDelegation
delegation -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GenesisDelegation
delegation
instance ToCBOR GenesisDelegation where
toCBOR :: GenesisDelegation -> Encoding
toCBOR = forall a. EncCBOR a => a -> Encoding
toByronCBOR
instance FromCBOR GenesisDelegation where
fromCBOR :: forall s. Decoder s GenesisDelegation
fromCBOR = forall a s. DecCBOR a => Decoder s a
fromByronCBOR
instance EncCBOR GenesisDelegation where
encCBOR :: GenesisDelegation -> Encoding
encCBOR (UnsafeGenesisDelegation Map KeyHash Certificate
gd) =
Word -> Encoding
encodeListLen Word
1
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR @(Map KeyHash Certificate) Map KeyHash Certificate
gd
instance DecCBOR GenesisDelegation where
decCBOR :: forall s. Decoder s GenesisDelegation
decCBOR = do
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"GenesisDelegation" Int
1
Map KeyHash Certificate -> GenesisDelegation
UnsafeGenesisDelegation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR @(Map KeyHash Certificate)
data GenesisDelegationError
= GenesisDelegationDuplicateIssuer
| GenesisDelegationInvalidKey KeyHash KeyHash
| GenesisDelegationMultiLayerDelegation KeyHash
deriving (GenesisDelegationError -> GenesisDelegationError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenesisDelegationError -> GenesisDelegationError -> Bool
$c/= :: GenesisDelegationError -> GenesisDelegationError -> Bool
== :: GenesisDelegationError -> GenesisDelegationError -> Bool
$c== :: GenesisDelegationError -> GenesisDelegationError -> Bool
Eq, Int -> GenesisDelegationError -> ShowS
[GenesisDelegationError] -> ShowS
GenesisDelegationError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenesisDelegationError] -> ShowS
$cshowList :: [GenesisDelegationError] -> ShowS
show :: GenesisDelegationError -> String
$cshow :: GenesisDelegationError -> String
showsPrec :: Int -> GenesisDelegationError -> ShowS
$cshowsPrec :: Int -> GenesisDelegationError -> ShowS
Show)
instance B.Buildable GenesisDelegationError where
build :: GenesisDelegationError -> Builder
build = \case
GenesisDelegationError
GenesisDelegationDuplicateIssuer ->
forall a. Format Builder a -> a
bprint
Format Builder Builder
"Encountered duplicate issuer VerificationKey while constructing GenesisDelegation."
GenesisDelegationInvalidKey KeyHash
k KeyHash
k' ->
forall a. Format Builder a -> a
bprint
( Format
(KeyHash -> KeyHash -> Builder) (KeyHash -> KeyHash -> Builder)
"Invalid key in GenesisDelegation map.\nExpected: "
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (KeyHash -> Builder) (KeyHash -> Builder)
"\nGot: "
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build
)
KeyHash
k
KeyHash
k'
GenesisDelegationMultiLayerDelegation KeyHash
k ->
forall a. Format Builder a -> a
bprint
( Format (KeyHash -> Builder) (KeyHash -> Builder)
"Encountered multi-layer delegation.\n"
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
" is a delegate and an issuer."
)
KeyHash
k
mkGenesisDelegation ::
MonadError GenesisDelegationError m => [Certificate] -> m GenesisDelegation
mkGenesisDelegation :: forall (m :: * -> *).
MonadError GenesisDelegationError m =>
[Certificate] -> m GenesisDelegation
mkGenesisDelegation [Certificate]
certs = do
((forall a. HasLength a => a -> Int
length forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a. ACertificate a -> VerificationKey
issuerVK forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Certificate]
certs) forall a. Eq a => a -> a -> Bool
== forall a. HasLength a => a -> Int
length [Certificate]
certs)
forall e (m :: * -> *). MonadError e m => Bool -> e -> m ()
`orThrowError` GenesisDelegationError
GenesisDelegationDuplicateIssuer
let res :: Map KeyHash Certificate
res = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(VerificationKey -> KeyHash
hashKey forall a b. (a -> b) -> a -> b
$ forall a. ACertificate a -> VerificationKey
issuerVK Certificate
cert, Certificate
cert) | Certificate
cert <- [Certificate]
certs]
forall (m :: * -> *).
MonadError GenesisDelegationError m =>
Map KeyHash Certificate -> m GenesisDelegation
recreateGenesisDelegation Map KeyHash Certificate
res
recreateGenesisDelegation ::
MonadError GenesisDelegationError m =>
Map KeyHash Certificate ->
m GenesisDelegation
recreateGenesisDelegation :: forall (m :: * -> *).
MonadError GenesisDelegationError m =>
Map KeyHash Certificate -> m GenesisDelegation
recreateGenesisDelegation Map KeyHash Certificate
certMap = do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall k a. Map k a -> [(k, a)]
M.toList Map KeyHash Certificate
certMap) forall a b. (a -> b) -> a -> b
$ \(KeyHash
k, Certificate
cert) -> do
let k' :: KeyHash
k' = VerificationKey -> KeyHash
hashKey forall a b. (a -> b) -> a -> b
$ forall a. ACertificate a -> VerificationKey
issuerVK Certificate
cert
(KeyHash
k forall a. Eq a => a -> a -> Bool
== KeyHash
k') forall e (m :: * -> *). MonadError e m => Bool -> e -> m ()
`orThrowError` KeyHash -> KeyHash -> GenesisDelegationError
GenesisDelegationInvalidKey KeyHash
k KeyHash
k'
let delegateId :: KeyHash
delegateId = VerificationKey -> KeyHash
hashKey forall a b. (a -> b) -> a -> b
$ forall a. ACertificate a -> VerificationKey
delegateVK Certificate
cert
(KeyHash
delegateId forall k a. Ord k => k -> Map k a -> Bool
`M.notMember` Map KeyHash Certificate
certMap)
forall e (m :: * -> *). MonadError e m => Bool -> e -> m ()
`orThrowError` KeyHash -> GenesisDelegationError
GenesisDelegationMultiLayerDelegation KeyHash
delegateId
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Map KeyHash Certificate -> GenesisDelegation
UnsafeGenesisDelegation Map KeyHash Certificate
certMap