|
| 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