Skip to content

Commit

Permalink
Add bieAccountIsSuspended field to BakerInfoEx
Browse files Browse the repository at this point in the history
We add the `bieAccountIsSuspended` field to `BakerInfoEx` to make the field
persistent together with the account.
  • Loading branch information
drsk committed Sep 2, 2024
1 parent 834a777 commit f704492
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 4 deletions.
25 changes: 22 additions & 3 deletions haskell-src/Concordium/Types/Accounts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ module Concordium.Types.Accounts (
BakerInfoEx (..),
bieBakerInfo,
bieBakerPoolInfo,
bieAccountIsSuspended,
coerceBakerInfoExV1,
PendingChangeEffective (..),
pendingChangeEffectiveTimestamp,
Expand Down Expand Up @@ -96,6 +97,7 @@ import qualified Concordium.Crypto.SHA256 as Hash
import Concordium.ID.Types
import Concordium.Types
import Concordium.Types.Accounts.Releases
import Concordium.Types.Conditionally
import Concordium.Types.Execution (DelegationTarget, OpenStatus)
import Concordium.Types.HashableTo

Expand Down Expand Up @@ -207,11 +209,13 @@ instance FromJSON BakerPoolInfo where
data BakerInfoEx (av :: AccountVersion) where
BakerInfoExV0 :: !BakerInfo -> BakerInfoEx 'AccountV0
BakerInfoExV1 ::
forall av.
(AVSupportsDelegation av) =>
{ -- | The baker ID and keys.
_bieBakerInfo :: !BakerInfo,
-- | The baker pool info.
_bieBakerPoolInfo :: !BakerPoolInfo
_bieBakerPoolInfo :: !BakerPoolInfo,
_bieAccountIsSuspended :: !(Conditionally (SupportsValidatorSuspension av) Bool)
} ->
BakerInfoEx av

Expand All @@ -230,9 +234,20 @@ bieBakerPoolInfo :: (AVSupportsDelegation av) => Lens' (BakerInfoEx av) BakerPoo
bieBakerPoolInfo =
lens _bieBakerPoolInfo (\bie x -> bie{_bieBakerPoolInfo = x})

-- | Lens for '_bieBakerIsSuspended'
{-# INLINE bieAccountIsSuspended #-}
bieAccountIsSuspended ::
(AVSupportsDelegation av) =>
Lens' (BakerInfoEx av) (Conditionally (SupportsValidatorSuspension av) Bool)
bieAccountIsSuspended =
lens _bieAccountIsSuspended (\bie x -> bie{_bieAccountIsSuspended = x})

-- | Coerce a 'BakerInfoEx' between two account versions that support delegation.
coerceBakerInfoExV1 ::
(AVSupportsDelegation av1, AVSupportsDelegation av2) =>
( AVSupportsDelegation av1,
AVSupportsDelegation av2,
AVSupportsValidatorSuspension av1 ~ AVSupportsValidatorSuspension av2
) =>
BakerInfoEx av1 ->
BakerInfoEx av2
coerceBakerInfoExV1 BakerInfoExV1{..} = BakerInfoExV1{..}
Expand All @@ -243,12 +258,16 @@ coerceBakerInfoExV1 BakerInfoExV1{..} = BakerInfoExV1{..}
-- 'BakerInfo' was used.
instance forall av. (IsAccountVersion av) => Serialize (BakerInfoEx av) where
put (BakerInfoExV0 bi) = put bi
put BakerInfoExV1{..} = put _bieBakerInfo >> put _bieBakerPoolInfo
put BakerInfoExV1{..} = do
put _bieBakerInfo
put _bieBakerPoolInfo
put _bieAccountIsSuspended
get = case delegationSupport @av of
SAVDelegationNotSupported -> BakerInfoExV0 <$> get
SAVDelegationSupported -> do
_bieBakerInfo <- get
_bieBakerPoolInfo <- get
_bieAccountIsSuspended <- get
return BakerInfoExV1{..}

instance HasBakerInfo (BakerInfoEx av) where
Expand Down
14 changes: 13 additions & 1 deletion haskell-src/Concordium/Types/ProtocolVersion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -179,9 +179,15 @@ module Concordium.Types.ProtocolVersion (
-- | Determine whether validators can be suspended/resumed. A validator with
-- a suspended account is in essence not participating in the consensus.
-- Its stake and delegators stay unchanged.
SupportsValidatorSuspension,
supportsValidatorSuspension,
sSupportsValidatorSuspension,
-- | Determine whether the protocol supports suspending/resuming of validators.
protocolSupportsSuspend,
-- | Deterimne whether a specific account version supports suspending/
-- resuming of validators.
AVSupportsValidatorSuspension,
PVSupportsValidatorSuspension,

-- * Block hash version

Expand Down Expand Up @@ -446,7 +452,7 @@ demoteProtocolVersion = fromSing

-- | Constraint on a type level 'AccountVersion' that can be used to get a corresponding
-- 'SAccountVersion' (see 'accountVersion'). (An alias for 'SingI'.)
type IsAccountVersion (av :: AccountVersion) = SingI av
type IsAccountVersion (av :: AccountVersion) = (SingI av, SingI (SupportsValidatorSuspension av))

-- | Constraint on a type level 'ChainParametersVersion' that can be used to get a corresponding
-- 'SChainParametersVersion' (see 'chainParametersVersion'). (An alias for 'SingI'.)
Expand Down Expand Up @@ -567,6 +573,12 @@ protocolSupportsSuspend spv = case sSupportsValidatorSuspension (sAccountVersion
STrue -> True
SFalse -> False

type AVSupportsValidatorSuspension (av :: AccountVersion) =
SupportsValidatorSuspension av ~ 'True

type PVSupportsValidatorSuspension (pv :: ProtocolVersion) =
AVSupportsValidatorSuspension (AccountVersionFor pv)

-- | Constraint that an account version supports flexible cooldown.
--
-- Note, we do not use 'Assert' here, since that results in a weaker constraint that requires
Expand Down

0 comments on commit f704492

Please sign in to comment.