Skip to content

Commit

Permalink
Move serialize/deserialize functions to LedgerEvent
Browse files Browse the repository at this point in the history
  • Loading branch information
abailly committed Sep 21, 2023
1 parent 522b773 commit b5624e3
Show file tree
Hide file tree
Showing 2 changed files with 41 additions and 10 deletions.
43 changes: 40 additions & 3 deletions cardano-node/src/Cardano/Node/LedgerEvent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PartialTypeSignatures #-}
Expand All @@ -22,16 +23,19 @@ module Cardano.Node.LedgerEvent (
ConvertLedgerEvent (..)
, EventsConstraints
, LedgerEvent (..)
, AnchoredEvent (..)
, fromAuxLedgerEvent
, convertPoolRewards
, ledgerEventName
, eventCodecVersion
, serializeEvent
, tailEvent
) where

import Cardano.Prelude hiding (All, Sum)

import Cardano.Ledger.Binary (DecCBOR(..), EncCBOR(..), Version, unsafeDeserialize)
import Cardano.Ledger.Binary (DecCBOR(..), EncCBOR(..), Version, serialize',
unsafeDeserialize)
import Cardano.Ledger.Binary.Coders (Decode(..), Encode (..), encode, (!>),
(<!), decode)
import Cardano.Ledger.Coin (Coin (..), DeltaCoin (..))
Expand All @@ -50,6 +54,7 @@ import Cardano.Ledger.Shelley.Rules (RupdEvent (..),
import Cardano.Slotting.Slot (SlotNo, EpochNo (..))
import Control.State.Transition (Event)
import Data.ByteString.Short(ShortByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Map.Strict as Map
import Data.SOP.Strict (All, K (..), NS(..), hcmap, hcollapse)
Expand All @@ -60,7 +65,7 @@ import Ouroboros.Consensus.Cardano.Block (AllegraEra, AlonzoEra,
BabbageEra, CardanoEras, ConwayEra, HardForkBlock,
MaryEra, ShelleyEra)
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
(OneEraLedgerEvent(..))
(OneEraLedgerEvent(..), OneEraHash(..))
import Ouroboros.Consensus.Ledger.Abstract (AuxLedgerEvent,
LedgerState)
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock,
Expand Down Expand Up @@ -438,11 +443,43 @@ pattern LERetiredPools r u e <-
)
)

data AnchoredEvent =
AnchoredEvent { headerHash :: ShortByteString
, slotNo :: SlotNo
, ledgerEvent :: LedgerEvent
}
deriving (Eq, Show)


instance EncCBOR AnchoredEvent where
encCBOR = encode . Rec

instance DecCBOR AnchoredEvent where
decCBOR =
decode $ RecD AnchoredEvent
<! From
<! From
<! From


serializeEvent :: Version -> AnchoredEvent -> ByteString
serializeEvent codecVersion AnchoredEvent{headerHash, slotNo, ledgerEvent} =
let bytes = serialize' codecVersion headerHash <>
serialize' codecVersion slotNo <>
serialize' codecVersion ledgerEvent

size = serialize' codecVersion (BS.length bytes)
in size <> bytes

deserializeEvent :: Version -> ByteString -> Maybe AnchoredEvent
deserializeEvent codecVersion bytes =
unsafeDeserialize codecVersion $ LBS.fromStrict $ BS.drop 5 bytes

-- IO action to read ledger events in binary form
tailEvent :: FilePath -> IO ()
tailEvent eventsDb =
withFile eventsDb ReadMode $ \ h -> do
let version = maxBound
len :: Word32 <- unsafeDeserialize version <$> LBS.hGet h 5
event :: (ShortByteString, SlotNo, LedgerEvent)<- unsafeDeserialize version <$> LBS.hGet h (fromIntegral len)
event :: (ShortByteString, SlotNo, LedgerEvent) <- trace ("length = " <> show @_ @Text len) $ unsafeDeserialize version <$> LBS.hGet h (fromIntegral len)
putStrLn $ "Ledger Event: " <> show @_ @Text event
8 changes: 1 addition & 7 deletions cardano-node/src/Cardano/Node/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -179,13 +179,7 @@ runNode cmdPc = do
handleNodeWithTracers
(case blk of
Api.CardanoBlockType -> LedgerEventHandler $ \headerHash slotNo event -> do
let codecVersion = eventCodecVersion event
bytes = serialize' codecVersion
( getOneEraHash headerHash
, slotNo
, fromAuxLedgerEvent event
)
BS.hPut h $ (serialize' codecVersion $ BS.length bytes) <> bytes
maybe (pure ()) (\ e -> BS.hPut h $ serializeEvent (eventCodecVersion event) (AnchoredEvent (getOneEraHash headerHash) slotNo e)) (fromAuxLedgerEvent event)
Api.ByronBlockType{} ->
discardEvent
Api.ShelleyBlockType{} ->
Expand Down

0 comments on commit b5624e3

Please sign in to comment.