Skip to content

Commit dd2a329

Browse files
committed
Add encoder and decoder for LedgerState
1 parent 63a9c42 commit dd2a329

File tree

3 files changed

+50
-0
lines changed

3 files changed

+50
-0
lines changed

cardano-api/cardano-api.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ library
7676
Cardano.Api.KeysShelley
7777
Cardano.Api.LedgerEvent
7878
Cardano.Api.LedgerState
79+
Cardano.Api.LedgerState.Serialisation
7980
Cardano.Api.Modes
8081
Cardano.Api.NetworkId
8182
Cardano.Api.OperationalCertificate

cardano-api/src/Cardano/Api.hs

+3
Original file line numberDiff line numberDiff line change
@@ -533,6 +533,8 @@ module Cardano.Api (
533533
envSecurityParam,
534534
LedgerState(..),
535535
initialLedgerState,
536+
encodeLedgerState,
537+
decodeLedgerState,
536538
applyBlock,
537539
ValidationMode(..),
538540

@@ -755,6 +757,7 @@ import Cardano.Api.KeysByron
755757
import Cardano.Api.KeysShelley
756758
import Cardano.Api.LedgerEvent
757759
import Cardano.Api.LedgerState
760+
import Cardano.Api.LedgerState.Serialisation
758761
import Cardano.Api.Modes
759762
import Cardano.Api.NetworkId
760763
import Cardano.Api.OperationalCertificate
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE RankNTypes #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
6+
module Cardano.Api.LedgerState.Serialisation
7+
( encodeLedgerState,
8+
decodeLedgerState,
9+
)
10+
where
11+
12+
import Prelude
13+
14+
import Cardano.Api.LedgerState (LedgerState (LedgerState))
15+
import qualified Codec.CBOR.Decoding as CBOR
16+
import qualified Codec.CBOR.Encoding as CBOR
17+
import Data.SOP.Strict (K (K), NP (Nil, (:*)), fn, type (:.:) (Comp))
18+
import qualified Ouroboros.Consensus.Byron.Ledger.Ledger as Byron
19+
import qualified Ouroboros.Consensus.HardFork.Combinator.Basics as HFC
20+
import qualified Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common as HFC
21+
import qualified Ouroboros.Consensus.Shelley.Ledger.Ledger as Shelley
22+
23+
encodeLedgerState :: LedgerState -> CBOR.Encoding
24+
encodeLedgerState (LedgerState (HFC.HardForkLedgerState st)) =
25+
HFC.encodeTelescope
26+
(byron :* shelley :* allegra :* mary :* alonzo :* babbage :* Nil)
27+
st
28+
where
29+
byron = fn (K . Byron.encodeByronLedgerState)
30+
shelley = fn (K . Shelley.encodeShelleyLedgerState)
31+
allegra = fn (K . Shelley.encodeShelleyLedgerState)
32+
mary = fn (K . Shelley.encodeShelleyLedgerState)
33+
alonzo = fn (K . Shelley.encodeShelleyLedgerState)
34+
babbage = fn (K . Shelley.encodeShelleyLedgerState)
35+
36+
decodeLedgerState :: forall s. CBOR.Decoder s LedgerState
37+
decodeLedgerState =
38+
LedgerState . HFC.HardForkLedgerState
39+
<$> HFC.decodeTelescope (byron :* shelley :* allegra :* mary :* alonzo :* babbage :* Nil)
40+
where
41+
byron = Comp Byron.decodeByronLedgerState
42+
shelley = Comp Shelley.decodeShelleyLedgerState
43+
allegra = Comp Shelley.decodeShelleyLedgerState
44+
mary = Comp Shelley.decodeShelleyLedgerState
45+
alonzo = Comp Shelley.decodeShelleyLedgerState
46+
babbage = Comp Shelley.decodeShelleyLedgerState

0 commit comments

Comments
 (0)