{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Cardano.Ledger.State.ChainAccount (
CanGetChainAccountState (..),
CanSetChainAccountState (..),
ChainAccountState (AccountState, asTreasury, asReserves, ..),
AccountState,
casTreasuryL,
casReservesL,
treasuryL,
reservesL,
) where
import Cardano.Ledger.Binary
import Cardano.Ledger.Coin
import Control.DeepSeq (NFData)
import Data.Aeson (KeyValue, ToJSON (..), object, pairs, (.=))
import Data.Default (Default (def))
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks)
class CanGetChainAccountState t where
chainAccountStateG :: SimpleGetter (t era) ChainAccountState
default chainAccountStateG :: CanSetChainAccountState t => SimpleGetter (t era) ChainAccountState
chainAccountStateG = forall (t :: * -> *) era.
CanSetChainAccountState t =>
Lens' (t era) ChainAccountState
chainAccountStateL
{-# INLINE chainAccountStateG #-}
class CanGetChainAccountState t => CanSetChainAccountState t where
chainAccountStateL :: Lens' (t era) ChainAccountState
type AccountState = ChainAccountState
pattern AccountState :: Coin -> Coin -> AccountState
pattern $bAccountState :: Coin -> Coin -> ChainAccountState
$mAccountState :: forall {r}.
ChainAccountState -> (Coin -> Coin -> r) -> ((# #) -> r) -> r
AccountState {ChainAccountState -> Coin
asTreasury, ChainAccountState -> Coin
asReserves} = ChainAccountState asTreasury asReserves
{-# DEPRECATED AccountState "In favor of `ChainAccountState`" #-}
{-# DEPRECATED asTreasury "In favor of `casTreasury`" #-}
{-# DEPRECATED asReserves "In favor of `casReserves`" #-}
data ChainAccountState = ChainAccountState
{ ChainAccountState -> Coin
casTreasury :: !Coin
, ChainAccountState -> Coin
casReserves :: !Coin
}
deriving (Int -> ChainAccountState -> ShowS
[ChainAccountState] -> ShowS
ChainAccountState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChainAccountState] -> ShowS
$cshowList :: [ChainAccountState] -> ShowS
show :: ChainAccountState -> String
$cshow :: ChainAccountState -> String
showsPrec :: Int -> ChainAccountState -> ShowS
$cshowsPrec :: Int -> ChainAccountState -> ShowS
Show, ChainAccountState -> ChainAccountState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChainAccountState -> ChainAccountState -> Bool
$c/= :: ChainAccountState -> ChainAccountState -> Bool
== :: ChainAccountState -> ChainAccountState -> Bool
$c== :: ChainAccountState -> ChainAccountState -> Bool
Eq, forall x. Rep ChainAccountState x -> ChainAccountState
forall x. ChainAccountState -> Rep ChainAccountState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChainAccountState x -> ChainAccountState
$cfrom :: forall x. ChainAccountState -> Rep ChainAccountState x
Generic)
instance EncCBOR ChainAccountState where
encCBOR :: ChainAccountState -> Encoding
encCBOR (ChainAccountState Coin
t Coin
r) =
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Coin
t forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Coin
r
instance DecCBOR ChainAccountState where
decCBOR :: forall s. Decoder s ChainAccountState
decCBOR =
forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed Text
"ChainAccountState" (forall a b. a -> b -> a
const Int
2) forall a b. (a -> b) -> a -> b
$ Coin -> Coin -> ChainAccountState
ChainAccountState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
instance ToJSON ChainAccountState where
toJSON :: ChainAccountState -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. KeyValue e a => ChainAccountState -> [a]
toChainAccountStatePairs
toEncoding :: ChainAccountState -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. KeyValue e a => ChainAccountState -> [a]
toChainAccountStatePairs
toChainAccountStatePairs :: KeyValue e a => ChainAccountState -> [a]
toChainAccountStatePairs :: forall e a. KeyValue e a => ChainAccountState -> [a]
toChainAccountStatePairs as :: ChainAccountState
as@(ChainAccountState Coin
_ Coin
_) =
let ChainAccountState {Coin
casTreasury :: Coin
casTreasury :: ChainAccountState -> Coin
casTreasury, Coin
casReserves :: Coin
casReserves :: ChainAccountState -> Coin
casReserves} = ChainAccountState
as
in [ Key
"treasury" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Coin
casTreasury
, Key
"reserves" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Coin
casReserves
]
instance NoThunks ChainAccountState
instance NFData ChainAccountState
instance Default ChainAccountState where
def :: ChainAccountState
def = Coin -> Coin -> ChainAccountState
ChainAccountState (Integer -> Coin
Coin Integer
0) (Integer -> Coin
Coin Integer
0)
casTreasuryL :: Lens' ChainAccountState Coin
casTreasuryL :: Lens' ChainAccountState Coin
casTreasuryL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ChainAccountState -> Coin
casTreasury (\ChainAccountState
ds Coin
u -> ChainAccountState
ds {casTreasury :: Coin
casTreasury = Coin
u})
{-# INLINE casTreasuryL #-}
casReservesL :: Lens' ChainAccountState Coin
casReservesL :: Lens' ChainAccountState Coin
casReservesL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ChainAccountState -> Coin
casReserves (\ChainAccountState
ds Coin
u -> ChainAccountState
ds {casReserves :: Coin
casReserves = Coin
u})
{-# INLINE casReservesL #-}
treasuryL :: CanSetChainAccountState t => Lens' (t era) Coin
treasuryL :: forall (t :: * -> *) era.
CanSetChainAccountState t =>
Lens' (t era) Coin
treasuryL = forall (t :: * -> *) era.
CanSetChainAccountState t =>
Lens' (t era) ChainAccountState
chainAccountStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ChainAccountState -> Coin
casTreasury (\ChainAccountState
ds Coin
u -> ChainAccountState
ds {casTreasury :: Coin
casTreasury = Coin
u})
{-# INLINE treasuryL #-}
reservesL :: CanSetChainAccountState t => Lens' (t era) Coin
reservesL :: forall (t :: * -> *) era.
CanSetChainAccountState t =>
Lens' (t era) Coin
reservesL = forall (t :: * -> *) era.
CanSetChainAccountState t =>
Lens' (t era) ChainAccountState
chainAccountStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ChainAccountState -> Coin
casReserves (\ChainAccountState
ds Coin
u -> ChainAccountState
ds {casReserves :: Coin
casReserves = Coin
u})
{-# INLINE reservesL #-}