From 62ca861dbe303cbcf522dd6ad2a2e2f8f7a3aa07 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 8 Oct 2025 14:24:36 -0700 Subject: [PATCH 001/119] LeiosDemo202510: draft Leios mini protocols I'm intentionally grouping this code poorly and avoiding comments in an attempt to emphasize that this code is currently being written to enable hacked-together prototypes, not as a contribution towards code that might run on mainnet. (Even though these definitions are much more compatible with that development work than is other code being written for this prototype.) --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 53 +++ ouroboros-consensus/ouroboros-consensus.cabal | 3 + .../LeiosDemoOnlyTestFetch.hs | 340 ++++++++++++++++++ .../LeiosDemoOnlyTestNotify.hs | 283 +++++++++++++++ 4 files changed, 679 insertions(+) create mode 100644 ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs create mode 100644 ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 03a006ea88..369ec21676 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -124,6 +124,8 @@ import Ouroboros.Network.TxSubmission.Mempool.Reader import Ouroboros.Network.TxSubmission.Outbound +import qualified Ouroboros.Network.Mux as ON + {------------------------------------------------------------------------------- Handlers -------------------------------------------------------------------------------} @@ -838,6 +840,28 @@ initiator miniProtocolParameters version versionData Apps {..} = }) version versionData + <> + mempty { ON.withHot = ON.WithHot [ + ON.MiniProtocol { + ON.miniProtocolNum = leiosNotifyMiniProtocolNum, + ON.miniProtocolStart = ON.StartOnDemand, + ON.miniProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte + }, + ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) + } + , ON.MiniProtocol { + ON.miniProtocolNum = leiosFetchMiniProtocolNum, + ON.miniProtocolStart = ON.StartOnDemand, + ON.miniProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes + }, + ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) + } + ] + } + where + addSafetyMargin x = x + x `div` 10 -- | A bi-directional network application. -- @@ -878,3 +902,32 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = }) version versionData + <> + mempty { ON.withHot = ON.WithHot [ + ON.MiniProtocol { + ON.miniProtocolNum = leiosNotifyMiniProtocolNum, + ON.miniProtocolStart = ON.StartOnDemand, + ON.miniProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte + }, + ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) + } + , ON.MiniProtocol { + ON.miniProtocolNum = leiosFetchMiniProtocolNum, + ON.miniProtocolStart = ON.StartOnDemand, + ON.miniProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes + }, + ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) + } + ] + } + where + addSafetyMargin x = x + x `div` 10 + + +leiosNotifyMiniProtocolNum :: MiniProtocolNum +leiosNotifyMiniProtocolNum = MiniProtocolNum 18 + +leiosFetchMiniProtocolNum :: MiniProtocolNum +leiosFetchMiniProtocolNum = MiniProtocolNum 19 diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index eea42167be..b1a5f434fa 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -67,6 +67,8 @@ library import: common-lib hs-source-dirs: src/ouroboros-consensus exposed-modules: + LeiosDemoOnlyTestFetch + LeiosDemoOnlyTestNotify Ouroboros.Consensus.Block Ouroboros.Consensus.Block.Abstract Ouroboros.Consensus.Block.EBB @@ -353,6 +355,7 @@ library transformers, transformers-base, typed-protocols ^>=0.3, + typed-protocols-cborg ^>=0.3, vector ^>=0.13, x-docspec-extra-packages: diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs new file mode 100644 index 0000000000..2562449f69 --- /dev/null +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -0,0 +1,340 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE StandaloneKindSignatures #-} +{-# LANGUAGE TypeFamilies #-} + +module LeiosDemoOnlyTestFetch + ( LeiosFetch (..) + , SingLeiosFetch (..) + , Message (..) + , byteLimitsLeiosFetch + , timeLimitsLeiosFetch + , codecLeiosFetch + , codecLeiosFetchId + ) where + +import qualified Codec.CBOR.Decoding as CBOR +import qualified Codec.CBOR.Encoding as CBOR +import qualified Codec.CBOR.Read as CBOR +import Control.DeepSeq (NFData (..)) +import Control.Monad.Class.MonadST +import Data.ByteString.Lazy (ByteString) +import Data.Kind (Type) +import Data.Singletons +import Data.Word (Word16, Word64) +import Network.TypedProtocol.Codec.CBOR +import Network.TypedProtocol.Core +import Ouroboros.Network.Protocol.Limits +import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) +import Text.Printf + +----- + +type LeiosFetch :: Type -> Type -> Type -> Type +data LeiosFetch point eb tx where + StIdle :: LeiosFetch point eb tx + StBlock :: LeiosFetch point eb tx + StBlockTxs :: LeiosFetch point eb tx + StDone :: LeiosFetch point eb tx + +instance ( ShowProxy point + , ShowProxy eb + , ShowProxy tx + ) + => ShowProxy (LeiosFetch point eb tx) where + showProxy _ = + concat + [ "LeiosFetch ", + showProxy (Proxy :: Proxy point), + " ", + showProxy (Proxy :: Proxy eb), + " ", + showProxy (Proxy :: Proxy tx) + ] + +instance ShowProxy (StIdle :: LeiosFetch point eb tx) where + showProxy _ = "StIdle" +instance ShowProxy (StBlock :: LeiosFetch point eb tx) where + showProxy _ = "StBlock" +instance ShowProxy (StBlockTxs :: LeiosFetch point eb tx) where + showProxy _ = "StBlockTxs" +instance ShowProxy (StDone :: LeiosFetch point eb tx) where + showProxy _ = "StDone" + +type SingLeiosFetch + :: LeiosFetch point eb tx + -> Type +data SingLeiosFetch st where + SingIdle :: SingLeiosFetch StIdle + SingBlock :: SingLeiosFetch StBlock + SingBlockTxs :: SingLeiosFetch StBlockTxs + SingDone :: SingLeiosFetch StDone + +deriving instance Show (SingLeiosFetch st) + +instance StateTokenI StIdle where stateToken = SingIdle +instance StateTokenI StBlock where stateToken = SingBlock +instance StateTokenI StBlockTxs where stateToken = SingBlockTxs +instance StateTokenI StDone where stateToken = SingDone + +----- + +instance Protocol (LeiosFetch point eb tx) where + data Message (LeiosFetch point eb tx) from to where + MsgLeiosBlockRequest + :: !point + -> Message (LeiosFetch point eb tx) StIdle StBlock + MsgLeiosBlock + :: !eb + -> Message (LeiosFetch point eb tx) StBlock StIdle + + MsgLeiosBlockTxsRequest + :: !point + -> [(Word16, Word64)] + -> Message (LeiosFetch point eb tx) StIdle StBlockTxs + MsgLeiosBlockTxs + :: ![tx] + -> Message (LeiosFetch point eb tx) StBlockTxs StIdle + + -- vote request + -- vote reply + + -- range request + -- range reply + + MsgDone + :: Message (LeiosFetch point eb tx) StIdle StDone + + type StateAgency StIdle = ClientAgency + type StateAgency StBlock = ServerAgency + type StateAgency StBlockTxs = ServerAgency + type StateAgency StDone = NobodyAgency + + type StateToken = SingLeiosFetch + +instance NFData (Message (LeiosFetch point eb tx) from to) where + rnf = \case + MsgLeiosBlockRequest{} -> () + MsgLeiosBlock{} -> () + MsgLeiosBlockTxsRequest _p bitmaps -> rnf bitmaps + MsgLeiosBlockTxs{} -> () + -- vote request + -- vote reply + -- range request + -- range reply + MsgDone -> () + +deriving instance (Eq point, Eq eb, Eq tx) + => Eq (Message (LeiosFetch point eb tx) from to) + +deriving instance (Show point, Show eb, Show tx) + => Show (Message (LeiosFetch point eb tx) from to) + +----- + +byteLimitsLeiosFetch + :: (bytes -> Word) -> ProtocolSizeLimits (LeiosFetch point eb tx) bytes +byteLimitsLeiosFetch = ProtocolSizeLimits $ \case + SingIdle -> smallByteLimit + SingBlock -> largeByteLimit + SingBlockTxs -> largeByteLimit + st@SingDone -> notActiveState st + +timeLimitsLeiosFetch + :: ProtocolTimeLimits (LeiosFetch point eb tx) +timeLimitsLeiosFetch = ProtocolTimeLimits $ \case + SingIdle -> waitForever + SingBlock -> longWait + SingBlockTxs -> longWait + st@SingDone -> notActiveState st + +----- + +codecLeiosFetch + :: forall (point :: Type) (eb :: Type) (tx :: Type) m. + (MonadST m) + => (point -> CBOR.Encoding) + -> (forall s. CBOR.Decoder s point) + -> (eb -> CBOR.Encoding) + -> (forall s. CBOR.Decoder s eb) + -> (tx -> CBOR.Encoding) + -> (forall s. CBOR.Decoder s tx) + -> Codec (LeiosFetch point eb tx) CBOR.DeserialiseFailure m ByteString +codecLeiosFetch encodeP decodeP encodeEb decodeEb encodeTx decodeTx = + mkCodecCborLazyBS + (encodeLeiosFetch encodeP encodeEb encodeTx) + decode + where + decode + :: forall (st :: LeiosFetch point eb tx). + (ActiveState st) + => StateToken st + -> forall s. CBOR.Decoder s (SomeMessage st) + decode stok = do + len <- CBOR.decodeListLen + key <- CBOR.decodeWord + decodeLeiosFetch decodeP decodeEb decodeTx stok len key + +encodeLeiosFetch + :: forall (point :: Type) (eb :: Type) (tx :: Type) + (st :: LeiosFetch point eb tx) + (st' :: LeiosFetch point eb tx). + (point -> CBOR.Encoding) + -> (eb -> CBOR.Encoding) + -> (tx -> CBOR.Encoding) + -> Message (LeiosFetch point eb tx) st st' + -> CBOR.Encoding +encodeLeiosFetch encodeP encodeEb encodeTx = encode + where + encode + :: forall st0 st1. + Message (LeiosFetch point eb tx) st0 st1 + -> CBOR.Encoding + encode = \case + MsgLeiosBlockRequest p -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 0 + <> encodeP p + MsgLeiosBlock x -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 1 + <> encodeEb x + MsgLeiosBlockTxsRequest p bitmaps -> + CBOR.encodeListLen 3 + <> CBOR.encodeWord 2 + <> encodeP p + <> encodeBitmaps bitmaps + MsgLeiosBlockTxs txs -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 3 + <> CBOR.encodeListLenIndef <> foldr (\tx r -> encodeTx tx <> r) CBOR.encodeBreak txs + -- vote request + -- vote reply + -- range request + -- range reply + MsgDone -> + CBOR.encodeListLen 1 + <> CBOR.encodeWord 8 + +decodeLeiosFetch + :: forall (point :: Type) (eb :: Type) (tx :: Type) + (st :: LeiosFetch point eb tx) s. + (ActiveState st) + => (forall s'. CBOR.Decoder s' point) + -> (forall s'. CBOR.Decoder s' eb) + -> (forall s'. CBOR.Decoder s' tx) + -> StateToken st + -> Int + -> Word + -> CBOR.Decoder s (SomeMessage st) +decodeLeiosFetch decodeP decodeEb decodeTx = decode + where + decode + :: forall (st' :: LeiosFetch point eb tx). + (ActiveState st') + => StateToken st' + -> Int + -> Word + -> CBOR.Decoder s (SomeMessage st') + decode stok len key = do + case (stok, len, key) of + (SingIdle, 1, 0) -> do + p <- decodeP + return $ SomeMessage $ MsgLeiosBlockRequest p + (SingBlock, 2, 1) -> do + x <- decodeEb + return $ SomeMessage $ MsgLeiosBlock x + (SingIdle, 3, 2) -> do + p <- decodeP + bitmaps <- decodeBitmaps + return $ SomeMessage $ MsgLeiosBlockTxsRequest p bitmaps + (SingBlockTxs, 2, 3) -> do + txs <- CBOR.decodeListLenIndef *> CBOR.decodeSequenceLenIndef (flip (:)) [] reverse decodeTx + return $ SomeMessage $ MsgLeiosBlockTxs txs + -- vote request + -- vote reply + -- range request + -- range reply + (SingIdle, 1, 8) -> + return $ SomeMessage MsgDone + (SingDone, _, _) -> notActiveState stok + -- failures per protocol state + (SingIdle, _, _) -> + fail $ printf "codecLeiosFetch (%s) unexpected key (%d, %d)" (show stok) key len + (SingBlock, _, _) -> + fail $ printf "codecLeiosFetch (%s) unexpected key (%d, %d)" (show stok) key len + (SingBlockTxs, _, _) -> + fail $ printf "codecLeiosFetch (%s) unexpected key (%d, %d)" (show stok) key len + +codecLeiosFetchId + :: forall (point :: Type) (eb :: Type) (tx :: Type) m. + (Monad m) + => Codec + (LeiosFetch point eb tx) + CodecFailure + m + (AnyMessage (LeiosFetch point eb tx)) +codecLeiosFetchId = Codec {encode, decode} + where + encode + :: forall st st'. + ( ActiveState st + , StateTokenI st + ) + => Message (LeiosFetch point eb tx) st st' + -> AnyMessage (LeiosFetch point eb tx) + encode = AnyMessage + + decode + :: forall (st :: LeiosFetch point eb tx). + (ActiveState st) + => StateToken st + -> m (DecodeStep + (AnyMessage (LeiosFetch point eb tx)) + CodecFailure + m + (SomeMessage st) + ) + decode stok = return $ DecodePartial $ \bytes -> + return $ case (stok, bytes) of + (SingIdle, Just (AnyMessage msg@MsgLeiosBlockRequest{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingBlock, Just (AnyMessage msg@MsgLeiosBlock{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingIdle, Just (AnyMessage msg@MsgLeiosBlockTxsRequest{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingBlockTxs, Just (AnyMessage msg@MsgLeiosBlockTxs{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingIdle, Just (AnyMessage msg@MsgDone{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingDone, _) -> + notActiveState stok + (_, _) -> + DecodeFail $ CodecFailure "codecLeiosFetchId: no matching message" + +----- + +encodeBitmaps :: [(Word16, Word64)] -> CBOR.Encoding +encodeBitmaps bitmaps = + CBOR.encodeMapLenIndef + <> foldr + (\(index, bitmap) r -> CBOR.encodeWord16 index <> CBOR.encodeWord64 bitmap <> r) + CBOR.encodeBreak + bitmaps + +decodeBitmaps :: CBOR.Decoder s [(Word16, Word64)] +decodeBitmaps = + CBOR.decodeMapLenIndef + *> CBOR.decodeSequenceLenIndef + (flip (:)) + [] + reverse + ((,) <$> CBOR.decodeWord16 <*> CBOR.decodeWord64) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs new file mode 100644 index 0000000000..bd90abc83f --- /dev/null +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -0,0 +1,283 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE StandaloneKindSignatures #-} +{-# LANGUAGE TypeFamilies #-} + +module LeiosDemoOnlyTestNotify + ( LeiosNotify (..) + , SingLeiosNotify (..) + , Message (..) + , byteLimitsLeiosNotify + , timeLimitsLeiosNotify + , codecLeiosNotify + , codecLeiosNotifyId + ) where + +import qualified Codec.CBOR.Decoding as CBOR +import qualified Codec.CBOR.Encoding as CBOR +import qualified Codec.CBOR.Read as CBOR +import Control.DeepSeq (NFData (..)) +import Control.Monad.Class.MonadST +import Data.ByteString.Lazy (ByteString) +import Data.Kind (Type) +import Data.Singletons +import Network.TypedProtocol.Codec.CBOR +import Network.TypedProtocol.Core +import Ouroboros.Network.Protocol.Limits +import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) +import Text.Printf + +----- + +type LeiosNotify :: Type -> Type -> Type +data LeiosNotify point announcement where + StIdle :: LeiosNotify point announcement + StBusy :: LeiosNotify point announcement + StDone :: LeiosNotify point announcement + +instance ( ShowProxy point + , ShowProxy announcement + ) + => ShowProxy (LeiosNotify point announcement) where + showProxy _ = + concat + [ "LeiosNotify ", + showProxy (Proxy :: Proxy point), + " ", + showProxy (Proxy :: Proxy announcement) + ] + +instance ShowProxy (StIdle :: LeiosNotify point announcement) where + showProxy _ = "StIdle" +instance ShowProxy (StBusy :: LeiosNotify point announcement) where + showProxy _ = "StBusy" +instance ShowProxy (StDone :: LeiosNotify point announcement) where + showProxy _ = "StDone" + +type SingLeiosNotify + :: LeiosNotify point announcement + -> Type +data SingLeiosNotify st where + SingIdle :: SingLeiosNotify StIdle + SingBusy :: SingLeiosNotify StBusy + SingDone :: SingLeiosNotify StDone + +deriving instance Show (SingLeiosNotify st) + +instance StateTokenI StIdle where stateToken = SingIdle +instance StateTokenI StBusy where stateToken = SingBusy +instance StateTokenI StDone where stateToken = SingDone + +----- + +instance Protocol (LeiosNotify point announcement) where + data Message (LeiosNotify point announcement) from to where + MsgLeiosNotificationRequestNext + :: Message (LeiosNotify point announcement) StIdle StBusy + + MsgLeiosBlockAnnouncement + :: !announcement + -> Message (LeiosNotify point announcement) StBusy StIdle + MsgLeiosBlockOffer + :: !point + -> Message (LeiosNotify point announcement) StBusy StIdle + MsgLeiosBlockTxsOffer + :: !point + -> Message (LeiosNotify point announcement) StBusy StIdle + -- votes offer + + MsgDone + :: Message (LeiosNotify point announcement) StIdle StDone + + type StateAgency StIdle = ClientAgency + type StateAgency StBusy = ServerAgency + type StateAgency StDone = NobodyAgency + + type StateToken = SingLeiosNotify + +instance NFData (Message (LeiosNotify point announcement) from to) where + rnf = \case + MsgLeiosNotificationRequestNext -> () + MsgLeiosBlockAnnouncement{} -> () + MsgLeiosBlockOffer{} -> () + MsgLeiosBlockTxsOffer{} -> () + -- votes offer + MsgDone -> () + +deriving instance (Eq point, Eq announcement) + => Eq (Message (LeiosNotify point announcement) from to) + +deriving instance (Show point, Show announcement) + => Show (Message (LeiosNotify point announcement) from to) + +----- + +byteLimitsLeiosNotify + :: (bytes -> Word) -> ProtocolSizeLimits (LeiosNotify point announcement) bytes +byteLimitsLeiosNotify = ProtocolSizeLimits $ \case + SingIdle -> smallByteLimit + SingBusy -> smallByteLimit + st@SingDone -> notActiveState st + +timeLimitsLeiosNotify + :: ProtocolTimeLimits (LeiosNotify point announcement) +timeLimitsLeiosNotify = ProtocolTimeLimits $ \case + SingIdle -> waitForever + SingBusy -> waitForever + st@SingDone -> notActiveState st + +----- + +codecLeiosNotify + :: forall (point :: Type) (announcement :: Type) m. + (MonadST m) + => (point -> CBOR.Encoding) + -> (forall s. CBOR.Decoder s point) + -> (announcement -> CBOR.Encoding) + -> (forall s. CBOR.Decoder s announcement) + -> Codec (LeiosNotify point announcement) CBOR.DeserialiseFailure m ByteString +codecLeiosNotify encodeP decodeP encodeA decodeA = + mkCodecCborLazyBS + (encodeLeiosNotify encodeP encodeA) + decode + where + decode + :: forall (st :: LeiosNotify point announcement). + (ActiveState st) + => StateToken st + -> forall s. CBOR.Decoder s (SomeMessage st) + decode stok = do + len <- CBOR.decodeListLen + key <- CBOR.decodeWord + decodeLeiosNotify decodeP decodeA stok len key + +encodeLeiosNotify + :: forall (point :: Type) (announcement :: Type) + (st :: LeiosNotify point announcement) + (st' :: LeiosNotify point announcement). + (point -> CBOR.Encoding) + -> (announcement -> CBOR.Encoding) + -> Message (LeiosNotify point announcement) st st' + -> CBOR.Encoding +encodeLeiosNotify encodeP encodeA = encode + where + encode + :: forall st0 st1. + Message (LeiosNotify point announcement) st0 st1 + -> CBOR.Encoding + encode = \case + MsgLeiosNotificationRequestNext -> + CBOR.encodeListLen 1 + <> CBOR.encodeWord 0 + MsgLeiosBlockAnnouncement x -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 1 + <> encodeA x + MsgLeiosBlockOffer p -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 2 + <> encodeP p + MsgLeiosBlockTxsOffer p -> + CBOR.encodeListLen 2 + <> CBOR.encodeWord 3 + <> encodeP p + -- votes offer + MsgDone -> + CBOR.encodeListLen 1 + <> CBOR.encodeWord 5 + +decodeLeiosNotify + :: forall (point :: Type) (announcement :: Type) + (st :: LeiosNotify point announcement) s. + (ActiveState st) + => (forall s'. CBOR.Decoder s' point) + -> (forall s'. CBOR.Decoder s' announcement) + -> StateToken st + -> Int + -> Word + -> CBOR.Decoder s (SomeMessage st) +decodeLeiosNotify decodeP decodeA = decode + where + decode + :: forall (st' :: LeiosNotify point announcement). + (ActiveState st') + => StateToken st' + -> Int + -> Word + -> CBOR.Decoder s (SomeMessage st') + decode stok len key = do + case (stok, len, key) of + (SingIdle, 1, 0) -> + return $ SomeMessage MsgLeiosNotificationRequestNext + (SingBusy, 2, 1) -> do + x <- decodeA + return $ SomeMessage $ MsgLeiosBlockAnnouncement x + (SingBusy, 2, 2) -> do + p <- decodeP + return $ SomeMessage $ MsgLeiosBlockOffer p + (SingBusy, 2, 3) -> do + p <- decodeP + return $ SomeMessage $ MsgLeiosBlockTxsOffer p + -- votes offer + (SingIdle, 1, 5) -> + return $ SomeMessage MsgDone + (SingDone, _, _) -> notActiveState stok + -- failures per protocol state + (SingIdle, _, _) -> + fail $ printf "codecLeiosNotify (%s) unexpected key (%d, %d)" (show stok) key len + (SingBusy, _, _) -> + fail $ printf "codecLeiosNotify (%s) unexpected key (%d, %d)" (show stok) key len + +codecLeiosNotifyId + :: forall (point :: Type) (announcement :: Type) m. + (Monad m) + => Codec + (LeiosNotify point announcement) + CodecFailure + m + (AnyMessage (LeiosNotify point announcement)) +codecLeiosNotifyId = Codec {encode, decode} + where + encode + :: forall st st'. + ( ActiveState st + , StateTokenI st + ) + => Message (LeiosNotify point announcement) st st' + -> AnyMessage (LeiosNotify point announcement) + encode = AnyMessage + + decode + :: forall (st :: LeiosNotify point announcement). + (ActiveState st) + => StateToken st + -> m (DecodeStep + (AnyMessage (LeiosNotify point announcement)) + CodecFailure + m + (SomeMessage st) + ) + decode stok = return $ DecodePartial $ \bytes -> + return $ case (stok, bytes) of + (SingIdle, Just (AnyMessage msg@MsgLeiosNotificationRequestNext)) -> + DecodeDone (SomeMessage msg) Nothing + (SingBusy, Just (AnyMessage msg@MsgLeiosBlockAnnouncement{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingBusy, Just (AnyMessage msg@MsgLeiosBlockOffer{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingBusy, Just (AnyMessage msg@MsgLeiosBlockTxsOffer{})) -> + DecodeDone (SomeMessage msg) Nothing + (SingIdle, Just (AnyMessage msg@MsgDone)) -> + DecodeDone (SomeMessage msg) Nothing + (SingDone, _) -> + notActiveState stok + (_, _) -> + DecodeFail $ CodecFailure "codecLeiosNotifyId: no matching message" From 12e5667b3e8f764eb055373943a9d922b56e9373 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 10 Oct 2025 17:37:22 -0300 Subject: [PATCH 002/119] Add the initial version of the demo script --- scripts/leios-demo/leios-october-demo.sh | 107 +++++++++++++++++++++++ 1 file changed, 107 insertions(+) create mode 100755 scripts/leios-demo/leios-october-demo.sh diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh new file mode 100755 index 0000000000..c7916ac1e3 --- /dev/null +++ b/scripts/leios-demo/leios-october-demo.sh @@ -0,0 +1,107 @@ +#!/bin/bash + +# The first parameter should be the path to the local checkout of +# cardano-node. +# +# The second parameter should be the path to the folder +# where the data of a benchmarking cluster run is stored +# (CLUSTER_RUN_DATA directory). + +# Local checkout path of the cardano-node repository +# Safely remove trailing slash if present +CARDANO_NODE_PATH="${1%/}" + +# P&T cluster run data +CLUSTER_RUN_DATA="${2%/}" + +if [ "$#" -ne 2 ]; then + echo "Error: Please provide two parameters: and ." >&2 + exit 1 +fi + +if [ ! -d "$CARDANO_NODE_PATH" ]; then + echo "Error: Cardano node path '$CARDANO_NODE_PATH' not found or is not a directory." >&2 + exit 1 +fi + +if [ ! -d "$CLUSTER_RUN_DATA" ]; then + echo "Error: CLUSTER_RUN_DATA directory '$CLUSTER_RUN_DATA' not found or is not a directory." >&2 + exit 1 +fi + +TMP_DIR=$(mktemp -d) +echo "Using temporary directory for DB and logs: $TMP_DIR" + +## +## Run immdb-server +## +IMMDB_CMD_CORE="cabal run immdb-server \ + -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ + --config $CLUSTER_RUN_DATA/node-0/config.json" + +echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" + +$IMMDB_CMD_CORE &> "$TMP_DIR/immdb-server.log" & + +IMMDB_SERVER_PID=$! + +echo "ImmDB server started with PID: $IMMDB_SERVER_PID" + +## +## Run cardano-node +## +pushd "$CARDANO_NODE_PATH" > /dev/null + +echo "Creating topology.json in $(pwd)" +cat << EOF > topology.json +{ + "bootstrapPeers": [], + "localRoots": [ + { + "accessPoints": [ + { + "address": "127.0.0.1", + "port": 3001 + } + ], + "advertise": false, + "trustable": true, + "valency": 1 + } + ], + "publicRoots": [] +} +EOF + +CARDANO_NODE_CMD_CORE="cabal run -- cardano-node run \ + --config $CLUSTER_RUN_DATA/node-0/config.json \ + --topology topology.json \ + --database-path $TMP_DIR/db \ + --socket-path node.socket \ + --host-addr 0.0.0.0 --port 3002" + +echo "Command: $CARDANO_NODE_CMD_CORE &> $TMP_DIR/cardano-node.log &" + +$CARDANO_NODE_CMD_CORE &> "$TMP_DIR/cardano-node.log" & + +CARDANO_NODE_PID=$! + +echo "Cardano node started with PID: $CARDANO_NODE_PID" + +# Return to the original directory +popd > /dev/null + +# TODO: we should change the condition on which we terminate the demo. +echo "Sleeping for 30 seconds" +sleep 30 + +echo "Killing processes $IMMDB_SERVER_PID (immdb-server) and $CARDANO_NODE_PID (cardano-node)..." + +kill "$IMMDB_SERVER_PID" 2>/dev/null || true + +# Use negative PID to target the process group ID and SIGKILL. +kill -9 -"$CARDANO_NODE_PID" 2>/dev/null || true + +echo "Temporary data stored at: $TMP_DIR" + +exit 0 From 7ebe7b5c7c1bdef95c3d963ffb53546458ec9b8f Mon Sep 17 00:00:00 2001 From: dnadales Date: Mon, 13 Oct 2025 17:13:40 -0300 Subject: [PATCH 003/119] Add node-0 to the path of different files ... such as topology, database, and socket. --- scripts/leios-demo/leios-october-demo.sh | 18 ++++++++++-------- 1 file changed, 10 insertions(+), 8 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index c7916ac1e3..ab4e866344 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -48,12 +48,12 @@ IMMDB_SERVER_PID=$! echo "ImmDB server started with PID: $IMMDB_SERVER_PID" ## -## Run cardano-node +## Run cardano-node (node-0) ## pushd "$CARDANO_NODE_PATH" > /dev/null -echo "Creating topology.json in $(pwd)" -cat << EOF > topology.json +echo "Creating topology-node-0.json in $(pwd)" +cat << EOF > topology-node-0.json { "bootstrapPeers": [], "localRoots": [ @@ -73,16 +73,18 @@ cat << EOF > topology.json } EOF +mkdir -p "$TMP_DIR/node-0/db" + CARDANO_NODE_CMD_CORE="cabal run -- cardano-node run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --topology topology.json \ - --database-path $TMP_DIR/db \ - --socket-path node.socket \ + --topology topology-node-0.json \ + --database-path $TMP_DIR/node-0/db \ + --socket-path node-0.socket \ --host-addr 0.0.0.0 --port 3002" -echo "Command: $CARDANO_NODE_CMD_CORE &> $TMP_DIR/cardano-node.log &" +echo "Command: $CARDANO_NODE_CMD_CORE &> $TMP_DIR/cardano-node-0.log &" -$CARDANO_NODE_CMD_CORE &> "$TMP_DIR/cardano-node.log" & +$CARDANO_NODE_CMD_CORE &> "$TMP_DIR/cardano-node-0.log" & CARDANO_NODE_PID=$! From 79d58e4d16e27fa1b4a543861cf8f8ca5e5d9ed9 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 13 Oct 2025 15:07:12 -0700 Subject: [PATCH 004/119] leiosdemo202510: add this demo exe --- ouroboros-consensus/app/leiosdemo202510.hs | 325 ++++++++++++++++++ ouroboros-consensus/ouroboros-consensus.cabal | 24 ++ 2 files changed, 349 insertions(+) create mode 100644 ouroboros-consensus/app/leiosdemo202510.hs diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs new file mode 100644 index 0000000000..975d38530f --- /dev/null +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -0,0 +1,325 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} + +module Main (main) where + +import Cardano.Binary (serialize') +import qualified Cardano.Crypto.Hash as Hash +import qualified Codec.CBOR.Encoding as CBOR +import Control.Monad (foldM, when) +import qualified Data.Aeson as JSON +import qualified Data.Bits as Bits +import Data.ByteString (ByteString) +import qualified Data.ByteString as BS +import qualified Data.ByteString.Base16 as BS16 +import qualified Data.ByteString.Lazy as BSL +import Data.Foldable (forM_) +import Data.List (intercalate, isSuffixOf, unfoldr) +import Data.String (fromString) +import qualified Data.Vector as V +import Data.Word (Word8, Word16, Word32, Word64) +import qualified Database.SQLite3.Direct as DB +import GHC.Generics (Generic) +import System.Directory (doesFileExist) +import System.Environment (getArgs) +import System.Exit (die) +import qualified System.Random as R +import qualified System.Random.Stateful as R +import Text.Read (readMaybe) + +main :: IO () +main = getArgs >>= \case + ["generate", dbPath, manifestPath] + | ".db" `isSuffixOf` dbPath + , ".json" `isSuffixOf` manifestPath + -> do + doesFileExist dbPath >>= \case + True -> die "database path must not exist" + False -> pure () + manifest <- fmap JSON.eitherDecode (BSL.readFile manifestPath) >>= \case + Left err -> die err + Right x -> pure x + db <- withDieMsg $ DB.open (fromString dbPath) + prng0 <- R.initStdGen + generateDb prng0 db manifest + "MsgLeiosBlockTxsRequest" : dbPath : ebSlotStr : ebHashStr : bitmapChunkStrs + | ".db" `isSuffixOf` dbPath + , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode (fromString ebHashStr :: ByteString) + , Just bitmaps <- parseBitmaps bitmapChunkStrs + -> do + db <- withDieMsg $ DB.open (fromString dbPath) + msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps + _ -> die "Either $0 generate myDatabase.db myManifest.json\n OR $0 MsgLeiosBlockTxsRequest ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ..." + +parseBitmaps :: [String] -> Maybe [(Word16, Word64)] +parseBitmaps = + go [] + where + go acc = \case + [] -> Just (reverse acc) + bitmapChunkStr : bitmapChunkStrs + | (idxStr, _:bitmapStr) <- break (==':') bitmapChunkStr + , Just idx <- readMaybe idxStr + , Just bitmap <- readMaybe bitmapStr + -> go ((idx, bitmap) : acc) bitmapChunkStrs + _ -> Nothing + +data EbRecipe = EbRecipe { + slotNo :: Word64 + , + txByteSizes :: V.Vector Word16 + } + deriving (Generic, Show) + +-- | defaults to @GHC.Generics@ +instance JSON.FromJSON EbRecipe where {} + +----- + +type HASH = Hash.Blake2b_256 + +generateDb :: R.RandomGen g => g -> DB.Database -> [EbRecipe] -> IO () +generateDb prng0 db ebRecipes = do + gref <- R.newIOGenM prng0 + -- init db + withDieMsg $ DB.exec db (fromString sql_schema) + stmt_insert_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoints) + stmt_insert_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBodies) + stmt_insert_ebClosures <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosures) + -- loop over EBs (one SQL transaction each, to be gentle) + forM_ ([(0 :: Word16) ..] `zip` ebRecipes) $ \(ebPoint, ebRecipe) -> do + -- generate txs, so we have their hashes + txs <- V.forM (txByteSizes ebRecipe) $ \txByteSize -> do + -- generate a random bytestring whose CBOR encoding has the expected length + -- + -- In the actual implementation, the values themselves will be + -- valid CBOR. It's useful to maintain that invariant even for the + -- otherwise-opaque random data within this prototype/demo. + when (txByteSize < 55) $ die "Tx cannot be smaller than 55 bytes" + let overhead -- one for the initial byte, plus 1 2 4 or 8 for the length argument + | txByteSize < fromIntegral (maxBound :: Word8) = 2 + | txByteSize < (maxBound :: Word16) = 3 + | txByteSize < fromIntegral (maxBound :: Word32) = 5 + | otherwise = 9 + txBytes <- R.uniformByteStringM (fromIntegral txByteSize - overhead) gref + let txCborBytes = serialize' $ CBOR.encodeBytes txBytes + pure (txCborBytes, Hash.hashWith id txCborBytes :: Hash.Hash HASH ByteString) + let ebSlot = slotNo ebRecipe + let ebHash :: Hash.Hash HASH ByteString + ebHash = Hash.castHash $ Hash.hashWithSerialiser encodeEB txs + withDieMsg $ DB.exec db (fromString "BEGIN") + withDie $ DB.bindInt64 stmt_insert_ebPoints 3 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_insert_ebClosures 1 (fromIntegral ebPoint) + -- INSERT INTO ebPoints + withDie $ DB.bindInt64 stmt_insert_ebPoints 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_insert_ebPoints 2 (Hash.hashToBytes ebHash) + withDieDone $ DB.stepNoCB stmt_insert_ebPoints + withDie $ DB.reset stmt_insert_ebPoints + -- loop over txs + V.iforM_ txs $ \txOffset (txCborBytes, txHash) -> do + withDie $ DB.bindInt64 stmt_insert_ebBodies 2 (fromIntegral txOffset) + withDie $ DB.bindInt64 stmt_insert_ebClosures 2 (fromIntegral txOffset) + -- INSERT INTO ebBodies + withDie $ DB.bindBlob stmt_insert_ebBodies 3 (Hash.hashToBytes txHash) + withDie $ DB.bindInt64 stmt_insert_ebBodies 4 (fromIntegral (BS.length txCborBytes)) + withDieDone $ DB.stepNoCB stmt_insert_ebBodies + withDie $ DB.reset stmt_insert_ebBodies + -- INSERT INTO ebClosures + withDie $ DB.bindBlob stmt_insert_ebClosures 3 txCborBytes + withDieDone $ DB.stepNoCB stmt_insert_ebClosures + withDie $ DB.reset stmt_insert_ebClosures + -- finalize each EB + withDieMsg $ DB.exec db (fromString "COMMIT") + -- finalize db + withDieMsg $ DB.exec db (fromString sql_index_schema) + +----- + +sql_schema :: String +sql_schema = + "CREATE TABLE txCache (\n\ + \ txHash BLOB NOT NULL PRIMARY KEY -- raw bytes\n\ + \ ,\n\ + \ txCborBytes BLOB NOT NULL -- in CBOR\n\ + \ ,\n\ + \ expiryUnixEpoch INTEGER NOT NULL\n\ + \ ) WITHOUT ROWID;\n\ + \\n\ + \CREATE TABLE ebPoints (\n\ + \ ebSlot INTEGER NOT NULL\n\ + \ ,\n\ + \ ebHash BLOB NOT NULL\n\ + \ ,\n\ + \ id INTEGER NOT NULL UNIQUE\n\ + \ ,\n\ + \ PRIMARY KEY (ebSlot, ebHash)\n\ + \ ) WITHOUT ROWID;\n\ + \\n\ + \CREATE TABLE ebBodies (\n\ + \ ebPoint INTEGER NOT NULL -- foreign key ebPoints.id\n\ + \ ,\n\ + \ txOffset INTEGER NOT NULL\n\ + \ ,\n\ + \ txHash BLOB NOT NULL -- raw bytes\n\ + \ ,\n\ + \ txSizeInBytes INTEGER NOT NULL\n\ + \ ,\n\ + \ missing BOOLEAN NOT NULL\n\ + \ ,\n\ + \ PRIMARY KEY (ebPoint, txOffset)\n\ + \ ) WITHOUT ROWID;\n\ + \\n\ + \CREATE TABLE ebClosures (\n\ + \ ebPoint INTEGER NOT NULL -- foreign key ebPoints.id\n\ + \ ,\n\ + \ txOffset INTEGER NOT NULL\n\ + \ ,\n\ + \ txCborBytes BLOB NOT NULL -- in CBOR\n\ + \ ,\n\ + \ PRIMARY KEY (ebPoint, txOffset)\n\ + \ ) WITHOUT ROWID;\n\ + \" + +sql_index_schema :: String +sql_index_schema = + "-- Helps with the eviction policy of the EbStore.\n\ + \CREATE INDEX ebPointsExpiry\n\ + \ ON ebPoints (ebSlot, id);\n\ + \\n\ + \-- Helps with the eviction policy of the TxCache.\n\ + \CREATE INDEX txCacheExpiry\n\ + \ ON txCache (expiryUnixEpoch, txHash);\n\ + \\n\ + \-- Helps with the eviction policy of the fetch logic's todo list.\n\ + \CREATE INDEX missingEbTxs\n\ + \ ON ebBodies (ebPoint, txOffset)\n\ + \ WHERE missing = TRUE;\n\ + \" + +sql_insert_ebPoints :: String +sql_insert_ebPoints = + "INSERT INTO ebPoints (ebSlot, ebHash, id) VALUES (?, ?, ?)\n\ + \" + +sql_insert_ebBodies :: String +sql_insert_ebBodies = + "INSERT INTO ebBodies (ebPoint, txOffset, txHash, txSizeInBytes, missing) VALUES (?, ?, ?, ?, FALSE)\n\ + \" + +sql_insert_ebClosures :: String +sql_insert_ebClosures = + "INSERT INTO ebClosures (ebPoint, txOffset, txCborBytes) VALUES (?, ?, ?)\n\ + \" + +sql_lookup_ebPoints :: String +sql_lookup_ebPoints = + "SELECT id FROM ebPoints WHERE ebSlot = ? AND ebHash = ?\n\ + \" + +sql_lookup_ebClosures :: Int -> String +sql_lookup_ebClosures n = + "SELECT txOffset, txCborBytes FROM ebClosures WHERE ebPoint = ? AND txOffset IN (" ++ hooks ++ ") ORDER BY txOffset\n\ + \" + where + hooks = intercalate ", " (replicate n "?") + +----- + +withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a +withDiePoly f io = + io >>= \case + Left e -> die $ show $ f e + Right x -> pure x + +withDieMsg :: IO (Either (DB.Error, DB.Utf8) a) -> IO a +withDieMsg = withDiePoly snd + +withDie :: IO (Either DB.Error a) -> IO a +withDie = withDiePoly id + +withDieDone :: IO (Either DB.Error DB.StepResult) -> IO () +withDieDone io = + withDie io >>= \case + DB.Row -> die "impossible!" + DB.Done -> pure () + +withDieJust :: IO (Either DB.Error (Maybe a)) -> IO a +withDieJust io = + withDie io >>= \case + Nothing -> die "impossible!" + Just x -> pure x + +----- + +encodeEbItem :: (ByteString, Hash.Hash HASH ByteString) -> CBOR.Encoding +encodeEbItem (txCborBytes, txHash) = + CBOR.encodeListLen 2 + <> CBOR.encodeBytes (Hash.hashToBytes txHash) + <> CBOR.encodeWord16 (fromIntegral (BS.length txCborBytes)) + +encodeEB :: Foldable f => f (ByteString, Hash.Hash HASH ByteString) -> CBOR.Encoding +encodeEB ebItems = + CBOR.encodeListLenIndef <> foldr (\x r -> encodeEbItem x <> r) CBOR.encodeBreak ebItems + +----- + +msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () +msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do + let nextOffset = \case + [] -> Nothing + (idx, bitmap) : k -> case popOffset bitmap of + Nothing -> nextOffset k + Just (i, bitmap') -> + Just (64 * fromIntegral idx + i, (idx, bitmap') : k) + offsets = unfoldr nextOffset bitmaps + -- find ebPoint (TODO combine this step via a JOIN?) + stmt_lookup_ebPoint <- withDieJust $ DB.prepare db (fromString sql_lookup_ebPoints) + withDie $ DB.bindInt64 stmt_lookup_ebPoint 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_lookup_ebPoint 2 ebHash + ebPoint <- withDie (DB.stepNoCB stmt_lookup_ebPoint) >>= \case + DB.Done -> die "No such EB" + DB.Row -> DB.columnInt64 stmt_lookup_ebPoint 0 + withDieDone $ DB.stepNoCB stmt_lookup_ebPoint + -- get the txs + stmt_lookup_ebClosures <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (length offsets) + withDie $ DB.bindInt64 stmt_lookup_ebClosures 1 ebPoint + forM_ ([(2 :: DB.ParamIndex) ..] `zip` offsets) $ \(i, offset) -> do + withDie $ DB.bindInt64 stmt_lookup_ebClosures i (fromIntegral offset) + acc <- (\f -> foldM f [] offsets) $ \acc offset -> do + withDie (DB.stepNoCB stmt_lookup_ebClosures) >>= \case + DB.Done -> die $ "No rows starting at offset: " ++ show offset + DB.Row -> do + txOffset <- DB.columnInt64 stmt_lookup_ebClosures 0 + txCborBytes <- DB.columnBlob stmt_lookup_ebClosures 1 + when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset + pure (txCborBytes : acc) + -- combine the txs + BS.putStr + $ BS16.encode + $ serialize' + $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak (reverse acc) + putStrLn "" + +{- | For example +@ + print $ unfoldr popOffset 0 + print $ unfoldr popOffset 1 + print $ unfoldr popOffset (2^ (33 :: Int)) + print $ unfoldr popOffset (16 + 2^ (63 :: Int)) + [] + [63] + [30] + [0,59] +@ +-} +popOffset :: Word64 -> Maybe (Int, Word64) +{-# INLINE popOffset #-} +popOffset = \case + 0 -> Nothing + w -> let zs = Bits.countLeadingZeros w + in + Just (zs, Bits.clearBit w (63 - zs)) diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index b1a5f434fa..18ceb09b9d 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -842,3 +842,27 @@ test-suite doctest build-depends: base, latex-svg-image, + +common common-exe + import: common-lib + ghc-options: + -threaded + -rtsopts + "-with-rtsopts=-N -I0 -A16m" + +executable leiosdemo202510 + import: common-exe + hs-source-dirs: app + main-is: leiosdemo202510.hs + build-depends: + aeson, + base, + base16-bytestring, + bytestring, + cardano-binary, + cardano-crypto-class, + cborg, + direct-sqlite, + directory, + random, + vector, From 97a4949720117aeaaa562d01a70d5d7df5490307 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 13 Oct 2025 15:12:30 -0700 Subject: [PATCH 005/119] leiosdemo202510: combine via join --- ouroboros-consensus/app/leiosdemo202510.hs | 22 ++++++---------------- 1 file changed, 6 insertions(+), 16 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 975d38530f..9f8c25a541 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -215,14 +215,11 @@ sql_insert_ebClosures = "INSERT INTO ebClosures (ebPoint, txOffset, txCborBytes) VALUES (?, ?, ?)\n\ \" -sql_lookup_ebPoints :: String -sql_lookup_ebPoints = - "SELECT id FROM ebPoints WHERE ebSlot = ? AND ebHash = ?\n\ - \" - sql_lookup_ebClosures :: Int -> String sql_lookup_ebClosures n = - "SELECT txOffset, txCborBytes FROM ebClosures WHERE ebPoint = ? AND txOffset IN (" ++ hooks ++ ") ORDER BY txOffset\n\ + "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ + \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ + \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ") ORDER BY ebClosures.txOffset\n\ \" where hooks = intercalate ", " (replicate n "?") @@ -276,18 +273,11 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) offsets = unfoldr nextOffset bitmaps - -- find ebPoint (TODO combine this step via a JOIN?) - stmt_lookup_ebPoint <- withDieJust $ DB.prepare db (fromString sql_lookup_ebPoints) - withDie $ DB.bindInt64 stmt_lookup_ebPoint 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_lookup_ebPoint 2 ebHash - ebPoint <- withDie (DB.stepNoCB stmt_lookup_ebPoint) >>= \case - DB.Done -> die "No such EB" - DB.Row -> DB.columnInt64 stmt_lookup_ebPoint 0 - withDieDone $ DB.stepNoCB stmt_lookup_ebPoint -- get the txs stmt_lookup_ebClosures <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (length offsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosures 1 ebPoint - forM_ ([(2 :: DB.ParamIndex) ..] `zip` offsets) $ \(i, offset) -> do + withDie $ DB.bindInt64 stmt_lookup_ebClosures 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_lookup_ebClosures 2 ebHash + forM_ ([(3 :: DB.ParamIndex) ..] `zip` offsets) $ \(i, offset) -> do withDie $ DB.bindInt64 stmt_lookup_ebClosures i (fromIntegral offset) acc <- (\f -> foldM f [] offsets) $ \acc offset -> do withDie (DB.stepNoCB stmt_lookup_ebClosures) >>= \case From 1e7141666317f1e4cd1fd37bd4989a4ea47dcffe Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 13 Oct 2025 15:19:40 -0700 Subject: [PATCH 006/119] leiosdemo202510: suggestive check on MsgLeiosBlockTxsRequest --- ouroboros-consensus/app/leiosdemo202510.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 9f8c25a541..86fff1ac88 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -266,6 +266,8 @@ encodeEB ebItems = msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do + when (not $ let idxs = map fst bitmaps in and $ zipWith (<) idxs (tail idxs)) $ do + die "Offsets not strictly ascending" let nextOffset = \case [] -> Nothing (idx, bitmap) : k -> case popOffset bitmap of From f92cb19fbd56a01e6037c3e4787579023f5549e9 Mon Sep 17 00:00:00 2001 From: dnadales Date: Mon, 13 Oct 2025 23:58:10 -0300 Subject: [PATCH 007/119] Run a second Cardano node as downstream peer --- scripts/leios-demo/leios-october-demo.sh | 61 ++++++++++++++++++++---- 1 file changed, 52 insertions(+), 9 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index ab4e866344..09e7fb7907 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -47,10 +47,11 @@ IMMDB_SERVER_PID=$! echo "ImmDB server started with PID: $IMMDB_SERVER_PID" +pushd "$CARDANO_NODE_PATH" > /dev/null + ## ## Run cardano-node (node-0) ## -pushd "$CARDANO_NODE_PATH" > /dev/null echo "Creating topology-node-0.json in $(pwd)" cat << EOF > topology-node-0.json @@ -75,20 +76,61 @@ EOF mkdir -p "$TMP_DIR/node-0/db" -CARDANO_NODE_CMD_CORE="cabal run -- cardano-node run \ +CARDANO_NODE_CMD="cabal run -- cardano-node run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ --socket-path node-0.socket \ --host-addr 0.0.0.0 --port 3002" -echo "Command: $CARDANO_NODE_CMD_CORE &> $TMP_DIR/cardano-node-0.log &" +echo "Command: $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" + +$CARDANO_NODE_CMD &> "$TMP_DIR/cardano-node-0.log" & + +CARDANO_NODE_0_PID=$! + +echo "Cardano node 0 started with PID: $CARDANO_NODE_0_PID" + +## +## Run a second Cardano-node (To be eventually replaced by a mocked downstream node) +## + +cat << EOF > topology-node-1.json +{ + "bootstrapPeers": [], + "localRoots": [ + { + "accessPoints": [ + { + "address": "127.0.0.1", + "port": 3002 + } + ], + "advertise": false, + "trustable": true, + "valency": 1 + } + ], + "publicRoots": [] +} +EOF + +mkdir -p "$TMP_DIR/node-1/db" + +MOCKED_PEER_CMD="cabal run -- cardano-node run \ + --config $CLUSTER_RUN_DATA/node-0/config.json \ + --topology topology-node-1.json \ + --database-path $TMP_DIR/node-1/db \ + --socket-path node-1.socket \ + --host-addr 0.0.0.0 --port 3003" + +echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" -$CARDANO_NODE_CMD_CORE &> "$TMP_DIR/cardano-node-0.log" & +$MOCKED_PEER_CMD &> "$TMP_DIR/cardano-node-1.log" & -CARDANO_NODE_PID=$! +MOCKED_PEER_PID=$! -echo "Cardano node started with PID: $CARDANO_NODE_PID" +echo "Cardano node 1 started with PID: $MOCKED_PEER_PID" # Return to the original directory popd > /dev/null @@ -97,12 +139,13 @@ popd > /dev/null echo "Sleeping for 30 seconds" sleep 30 -echo "Killing processes $IMMDB_SERVER_PID (immdb-server) and $CARDANO_NODE_PID (cardano-node)..." +echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." kill "$IMMDB_SERVER_PID" 2>/dev/null || true -# Use negative PID to target the process group ID and SIGKILL. -kill -9 -"$CARDANO_NODE_PID" 2>/dev/null || true +# Use negative PID to target the process group ID and SIGKILL for cardano-node processes. +kill -9 -"$CARDANO_NODE_0_PID" 2>/dev/null || true +kill -9 -"$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" From 35af3c904ff5c77a4d5b475a1a4396ff2550a3c7 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 06:36:00 -0700 Subject: [PATCH 008/119] leiosdemo202510: add msgLeiosBlockRequest and also stub limit on popCount --- ouroboros-consensus/app/leiosdemo202510.hs | 104 ++++++++++++++++++--- 1 file changed, 90 insertions(+), 14 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 86fff1ac88..c24bb22577 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} @@ -44,6 +47,13 @@ main = getArgs >>= \case db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen generateDb prng0 db manifest + ["MsgLeiosBlockRequest", dbPath, ebSlotStr, ebHashStr] + | ".db" `isSuffixOf` dbPath + , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode (fromString ebHashStr :: ByteString) + -> do + db <- withDieMsg $ DB.open (fromString dbPath) + msgLeiosBlockRequest db ebSlot ebHash "MsgLeiosBlockTxsRequest" : dbPath : ebSlotStr : ebHashStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath , Just ebSlot <- readMaybe ebSlotStr @@ -52,7 +62,10 @@ main = getArgs >>= \case -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps - _ -> die "Either $0 generate myDatabase.db myManifest.json\n OR $0 MsgLeiosBlockTxsRequest ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ..." + _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ + \ OR $0 MsgLeiosBlockRequest myDatabase.db ebSlot ebHash(hex)\n\ + \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \" parseBitmaps :: [String] -> Maybe [(Word16, Word64)] parseBitmaps = @@ -109,7 +122,11 @@ generateDb prng0 db ebRecipes = do pure (txCborBytes, Hash.hashWith id txCborBytes :: Hash.Hash HASH ByteString) let ebSlot = slotNo ebRecipe let ebHash :: Hash.Hash HASH ByteString - ebHash = Hash.castHash $ Hash.hashWithSerialiser encodeEB txs + ebHash = + Hash.castHash + $ Hash.hashWithSerialiser + (encodeEB (fromIntegral . BS.length) Hash.hashToBytes) + txs withDieMsg $ DB.exec db (fromString "BEGIN") withDie $ DB.bindInt64 stmt_insert_ebPoints 3 (fromIntegral ebPoint) withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) @@ -215,11 +232,20 @@ sql_insert_ebClosures = "INSERT INTO ebClosures (ebPoint, txOffset, txCborBytes) VALUES (?, ?, ?)\n\ \" +sql_lookup_ebBodies :: String +sql_lookup_ebBodies = + "SELECT ebBodies.txHash, ebBodies.txSizeInBytes FROM ebBodies\n\ + \INNER JOIN ebPoints ON ebBodies.ebPoint = ebPoints.id\n\ + \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ?\n\ + \ORDER BY ebBodies.txOffset\n\ + \" + sql_lookup_ebClosures :: Int -> String sql_lookup_ebClosures n = "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ - \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ") ORDER BY ebClosures.txOffset\n\ + \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ")\n\ + \ORDER BY ebClosures.txOffset\n\ \" where hooks = intercalate ", " (replicate n "?") @@ -252,22 +278,72 @@ withDieJust io = ----- -encodeEbItem :: (ByteString, Hash.Hash HASH ByteString) -> CBOR.Encoding -encodeEbItem (txCborBytes, txHash) = +encodeEbItem :: (b -> Word16) -> (h -> ByteString) -> (b, h) -> CBOR.Encoding +encodeEbItem bytesToLen hashToBytes (txCborBytes, txHash) = CBOR.encodeListLen 2 - <> CBOR.encodeBytes (Hash.hashToBytes txHash) - <> CBOR.encodeWord16 (fromIntegral (BS.length txCborBytes)) + <> CBOR.encodeBytes (hashToBytes txHash) + <> CBOR.encodeWord16 (bytesToLen txCborBytes) -encodeEB :: Foldable f => f (ByteString, Hash.Hash HASH ByteString) -> CBOR.Encoding -encodeEB ebItems = - CBOR.encodeListLenIndef <> foldr (\x r -> encodeEbItem x <> r) CBOR.encodeBreak ebItems +encodeEB :: Foldable f => (b -> Word16) -> (h -> ByteString) -> f (b, h) -> CBOR.Encoding +encodeEB bytesToLen hashToBytes ebItems = + CBOR.encodeListLenIndef + <> foldr + (\x r -> encodeEbItem bytesToLen hashToBytes x <> r) + CBOR.encodeBreak + ebItems ----- +-- | helper for msgLeiosBlockRequest +-- +-- The @[a]@ is less than 1024 long. +-- +-- Each 'V.Vector' is exactly 1024. +data X a = X [V.Vector a] !Word16 [a] + +emptyX :: X a +emptyX = X [] 0 [] + +pushX :: a -> X a -> X a +pushX x (X vs n xs) = + if n < 1024 then X vs (n+1) (x : xs) else + X (V.fromList (reverse xs) : vs) 1 [x] + +-- | helper for msgLeiosBlockRequest +newtype Y a = Y [V.Vector a] + deriving (Functor, Foldable) + +finalizeX :: X a -> Y a +finalizeX (X vs _n xs) = Y $ reverse $ V.fromList (reverse xs) : vs + +msgLeiosBlockRequest :: DB.Database -> Word64 -> ByteString -> IO () +msgLeiosBlockRequest db ebSlot ebHash = do + -- get the EB items + stmt_lookup_ebBodies <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies) + withDie $ DB.bindInt64 stmt_lookup_ebBodies 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_lookup_ebBodies 2 ebHash + let loop !acc = do + withDie (DB.stepNoCB stmt_lookup_ebBodies) >>= \case + DB.Done -> pure $ finalizeX acc + DB.Row -> do + txHash <- DB.columnBlob stmt_lookup_ebBodies 0 + txSizeInBytes <- DB.columnInt64 stmt_lookup_ebBodies 1 + loop $ pushX (txSizeInBytes, txHash) acc + y <- loop emptyX + -- combine the EB items + BS.putStr + $ BS16.encode + $ serialize' + $ encodeEB fromIntegral id y + putStrLn "" + msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do when (not $ let idxs = map fst bitmaps in and $ zipWith (<) idxs (tail idxs)) $ do die "Offsets not strictly ascending" + when (1000 < sum (map (Bits.popCount . snd) bitmaps)) $ do + -- TODO insert into temp table and join? + die "Too many offsets in one request" let nextOffset = \case [] -> Nothing (idx, bitmap) : k -> case popOffset bitmap of @@ -300,12 +376,12 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do @ print $ unfoldr popOffset 0 print $ unfoldr popOffset 1 - print $ unfoldr popOffset (2^ (33 :: Int)) - print $ unfoldr popOffset (16 + 2^ (63 :: Int)) + print $ unfoldr popOffset (2^(34 :: Int)) + print $ unfoldr popOffset (2^(63 :: Int) + 2^(62 :: Int) + 8) [] [63] - [30] - [0,59] + [29] + [0,1,60] @ -} popOffset :: Word64 -> Maybe (Int, Word64) From f514ce07449abc2d3386ae428dd8fdbc0cf2f80e Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 06:37:22 -0700 Subject: [PATCH 009/119] leiosdemo202510: relocate SQL definitions near use --- ouroboros-consensus/app/leiosdemo202510.hs | 36 +++++++++++----------- 1 file changed, 18 insertions(+), 18 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index c24bb22577..d608a8bca2 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -232,24 +232,6 @@ sql_insert_ebClosures = "INSERT INTO ebClosures (ebPoint, txOffset, txCborBytes) VALUES (?, ?, ?)\n\ \" -sql_lookup_ebBodies :: String -sql_lookup_ebBodies = - "SELECT ebBodies.txHash, ebBodies.txSizeInBytes FROM ebBodies\n\ - \INNER JOIN ebPoints ON ebBodies.ebPoint = ebPoints.id\n\ - \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ?\n\ - \ORDER BY ebBodies.txOffset\n\ - \" - -sql_lookup_ebClosures :: Int -> String -sql_lookup_ebClosures n = - "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ - \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ - \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ")\n\ - \ORDER BY ebClosures.txOffset\n\ - \" - where - hooks = intercalate ", " (replicate n "?") - ----- withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a @@ -337,6 +319,14 @@ msgLeiosBlockRequest db ebSlot ebHash = do $ encodeEB fromIntegral id y putStrLn "" +sql_lookup_ebBodies :: String +sql_lookup_ebBodies = + "SELECT ebBodies.txHash, ebBodies.txSizeInBytes FROM ebBodies\n\ + \INNER JOIN ebPoints ON ebBodies.ebPoint = ebPoints.id\n\ + \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ?\n\ + \ORDER BY ebBodies.txOffset\n\ + \" + msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do when (not $ let idxs = map fst bitmaps in and $ zipWith (<) idxs (tail idxs)) $ do @@ -391,3 +381,13 @@ popOffset = \case w -> let zs = Bits.countLeadingZeros w in Just (zs, Bits.clearBit w (63 - zs)) + +sql_lookup_ebClosures :: Int -> String +sql_lookup_ebClosures n = + "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ + \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ + \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ")\n\ + \ORDER BY ebClosures.txOffset\n\ + \" + where + hooks = intercalate ", " (replicate n "?") From cc158043558b0c8c0d3559fe63358f2b38bb00ff Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 14 Oct 2025 16:03:47 +0200 Subject: [PATCH 010/119] Scaffold leios-mvd NixOS test with leios-node --- flake.lock | 2704 +++++++++++++++-- flake.nix | 5 +- nix/leios-mvd/genesis/genesis.alonzo.json | 188 ++ nix/leios-mvd/genesis/genesis.byron.json | 42 + nix/leios-mvd/genesis/genesis.conway.json | 337 ++ nix/leios-mvd/genesis/genesis.shelley.json | 97 + nix/leios-mvd/leios-node/config.json | 279 ++ nix/leios-mvd/leios-node/delegate.key | 1 + nix/leios-mvd/leios-node/delegation-cert.json | 8 + nix/leios-mvd/leios-node/kes.skey | 5 + nix/leios-mvd/leios-node/kes.vkey | 5 + nix/leios-mvd/leios-node/opcert | 5 + nix/leios-mvd/leios-node/os.nix | 25 + nix/leios-mvd/leios-node/topology.json | 18 + nix/leios-mvd/leios-node/vrf.skey | 5 + nix/leios-mvd/leios-node/vrf.vkey | 5 + nix/leios-mvd/test.nix | 14 + 17 files changed, 3406 insertions(+), 337 deletions(-) create mode 100644 nix/leios-mvd/genesis/genesis.alonzo.json create mode 100644 nix/leios-mvd/genesis/genesis.byron.json create mode 100644 nix/leios-mvd/genesis/genesis.conway.json create mode 100644 nix/leios-mvd/genesis/genesis.shelley.json create mode 100644 nix/leios-mvd/leios-node/config.json create mode 100644 nix/leios-mvd/leios-node/delegate.key create mode 100644 nix/leios-mvd/leios-node/delegation-cert.json create mode 100755 nix/leios-mvd/leios-node/kes.skey create mode 100644 nix/leios-mvd/leios-node/kes.vkey create mode 100644 nix/leios-mvd/leios-node/opcert create mode 100644 nix/leios-mvd/leios-node/os.nix create mode 100644 nix/leios-mvd/leios-node/topology.json create mode 100755 nix/leios-mvd/leios-node/vrf.skey create mode 100644 nix/leios-mvd/leios-node/vrf.vkey create mode 100644 nix/leios-mvd/test.nix diff --git a/flake.lock b/flake.lock index 6997cbaa1f..27aca49dcf 100644 --- a/flake.lock +++ b/flake.lock @@ -17,6 +17,40 @@ "type": "github" } }, + "CHaP_2": { + "flake": false, + "locked": { + "lastModified": 1732742574, + "narHash": "sha256-XUhDWQeChjNPcYluz8sCbs5vW+3jEYysxEhpKdFXbt0=", + "owner": "IntersectMBO", + "repo": "cardano-haskell-packages", + "rev": "375a4694472aa362b7abba0e8b7f3de787e90c91", + "type": "github" + }, + "original": { + "owner": "IntersectMBO", + "ref": "repo", + "repo": "cardano-haskell-packages", + "type": "github" + } + }, + "CHaP_3": { + "flake": false, + "locked": { + "lastModified": 1752755491, + "narHash": "sha256-LhTRY6kgvg5cGfoQ9FD2v15WucqO4C+VLMHa9JP/Zi4=", + "owner": "intersectmbo", + "repo": "cardano-haskell-packages", + "rev": "fe5f8c99284ca892efe46d91a9ccb00aa76f2525", + "type": "github" + }, + "original": { + "owner": "intersectmbo", + "ref": "repo", + "repo": "cardano-haskell-packages", + "type": "github" + } + }, "HTTP": { "flake": false, "locked": { @@ -33,6 +67,38 @@ "type": "github" } }, + "HTTP_2": { + "flake": false, + "locked": { + "lastModified": 1451647621, + "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", + "owner": "phadej", + "repo": "HTTP", + "rev": "9bc0996d412fef1787449d841277ef663ad9a915", + "type": "github" + }, + "original": { + "owner": "phadej", + "repo": "HTTP", + "type": "github" + } + }, + "HTTP_3": { + "flake": false, + "locked": { + "lastModified": 1451647621, + "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", + "owner": "phadej", + "repo": "HTTP", + "rev": "9bc0996d412fef1787449d841277ef663ad9a915", + "type": "github" + }, + "original": { + "owner": "phadej", + "repo": "HTTP", + "type": "github" + } + }, "agda-nixpkgs": { "locked": { "lastModified": 1726583932, @@ -49,7 +115,43 @@ "type": "github" } }, + "blockfrost": { + "inputs": { + "nixpkgs": "nixpkgs" + }, + "locked": { + "lastModified": 1749464997, + "narHash": "sha256-9FFC13FH7LeT2izPrYgCgDpj2vhxGwIpuGMKNQlBZXU=", + "owner": "blockfrost", + "repo": "blockfrost-backend-ryo", + "rev": "7400007a369d34bbdb88ae1b576b89b4bb528b7f", + "type": "github" + }, + "original": { + "owner": "blockfrost", + "ref": "v4.1.2", + "repo": "blockfrost-backend-ryo", + "type": "github" + } + }, "blst": { + "flake": false, + "locked": { + "lastModified": 1739372843, + "narHash": "sha256-IlbNMLBjs/dvGogcdbWQIL+3qwy7EXJbIDpo4xBd4bY=", + "owner": "supranational", + "repo": "blst", + "rev": "8c7db7fe8d2ce6e76dc398ebd4d475c0ec564355", + "type": "github" + }, + "original": { + "owner": "supranational", + "ref": "v0.3.14", + "repo": "blst", + "type": "github" + } + }, + "blst_2": { "flake": false, "locked": { "lastModified": 1691598027, @@ -83,479 +185,1787 @@ "type": "github" } }, - "cabal-34": { + "cabal-32_2": { "flake": false, "locked": { - "lastModified": 1645834128, - "narHash": "sha256-wG3d+dOt14z8+ydz4SL7pwGfe7SiimxcD/LOuPCV6xM=", + "lastModified": 1603716527, + "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", "owner": "haskell", "repo": "cabal", - "rev": "5ff598c67f53f7c4f48e31d722ba37172230c462", + "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.2", "repo": "cabal", "type": "github" } }, - "cabal-36": { + "cabal-32_3": { "flake": false, "locked": { - "lastModified": 1669081697, - "narHash": "sha256-I5or+V7LZvMxfbYgZATU4awzkicBwwok4mVoje+sGmU=", + "lastModified": 1603716527, + "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", "owner": "haskell", "repo": "cabal", - "rev": "8fd619e33d34924a94e691c5fea2c42f0fc7f144", + "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.6", + "ref": "3.2", "repo": "cabal", "type": "github" } }, - "cabal-extras": { + "cabal-34": { "flake": false, "locked": { - "lastModified": 1719942255, - "narHash": "sha256-UbNZASD2xUk1S/z7yJ+k41kl523MZQW5t2wtPwemUhM=", - "owner": "phadej", - "repo": "cabal-extras", - "rev": "67a889582e7ef118f1c26b8f105abd2120f84fd0", + "lastModified": 1645834128, + "narHash": "sha256-wG3d+dOt14z8+ydz4SL7pwGfe7SiimxcD/LOuPCV6xM=", + "owner": "haskell", + "repo": "cabal", + "rev": "5ff598c67f53f7c4f48e31d722ba37172230c462", "type": "github" }, "original": { - "owner": "phadej", - "ref": "cabal-docspec-0.0.0.20240703", - "repo": "cabal-extras", + "owner": "haskell", + "ref": "3.4", + "repo": "cabal", "type": "github" } }, - "cardano-shell": { + "cabal-34_2": { "flake": false, "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", + "lastModified": 1645834128, + "narHash": "sha256-wG3d+dOt14z8+ydz4SL7pwGfe7SiimxcD/LOuPCV6xM=", + "owner": "haskell", + "repo": "cabal", + "rev": "5ff598c67f53f7c4f48e31d722ba37172230c462", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", + "owner": "haskell", + "ref": "3.4", + "repo": "cabal", "type": "github" } }, - "flake-compat": { + "cabal-34_3": { "flake": false, "locked": { - "lastModified": 1717312683, - "narHash": "sha256-FrlieJH50AuvagamEvWMIE6D2OAnERuDboFDYAED/dE=", - "owner": "nix-community", - "repo": "flake-compat", - "rev": "38fd3954cf65ce6faf3d0d45cd26059e059f07ea", + "lastModified": 1645834128, + "narHash": "sha256-wG3d+dOt14z8+ydz4SL7pwGfe7SiimxcD/LOuPCV6xM=", + "owner": "haskell", + "repo": "cabal", + "rev": "5ff598c67f53f7c4f48e31d722ba37172230c462", "type": "github" }, "original": { - "owner": "nix-community", - "repo": "flake-compat", + "owner": "haskell", + "ref": "3.4", + "repo": "cabal", "type": "github" } }, - "flake-compat_2": { + "cabal-36": { "flake": false, "locked": { - "lastModified": 1672831974, - "narHash": "sha256-z9k3MfslLjWQfnjBtEtJZdq3H7kyi2kQtUThfTgdRk0=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "45f2638735f8cdc40fe302742b79f248d23eb368", + "lastModified": 1669081697, + "narHash": "sha256-I5or+V7LZvMxfbYgZATU4awzkicBwwok4mVoje+sGmU=", + "owner": "haskell", + "repo": "cabal", + "rev": "8fd619e33d34924a94e691c5fea2c42f0fc7f144", "type": "github" }, "original": { - "owner": "input-output-hk", - "ref": "hkm/gitlab-fix", - "repo": "flake-compat", + "owner": "haskell", + "ref": "3.6", + "repo": "cabal", "type": "github" } }, - "flake-utils": { - "inputs": { - "systems": "systems" + "cabal-36_2": { + "flake": false, + "locked": { + "lastModified": 1669081697, + "narHash": "sha256-I5or+V7LZvMxfbYgZATU4awzkicBwwok4mVoje+sGmU=", + "owner": "haskell", + "repo": "cabal", + "rev": "8fd619e33d34924a94e691c5fea2c42f0fc7f144", + "type": "github" }, + "original": { + "owner": "haskell", + "ref": "3.6", + "repo": "cabal", + "type": "github" + } + }, + "cabal-36_3": { + "flake": false, "locked": { - "lastModified": 1710146030, - "narHash": "sha256-SZ5L6eA7HJ/nmkzGG7/ISclqe6oZdOZTNoesiInkXPQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "b1d9ab70662946ef0850d488da1c9019f3a9752a", + "lastModified": 1669081697, + "narHash": "sha256-I5or+V7LZvMxfbYgZATU4awzkicBwwok4mVoje+sGmU=", + "owner": "haskell", + "repo": "cabal", + "rev": "8fd619e33d34924a94e691c5fea2c42f0fc7f144", "type": "github" }, "original": { - "owner": "numtide", - "repo": "flake-utils", + "owner": "haskell", + "ref": "3.6", + "repo": "cabal", "type": "github" } }, - "gentle-introduction": { + "cabal-extras": { "flake": false, "locked": { - "lastModified": 1719935136, - "narHash": "sha256-CJQHzxMyyw62tzkBMbymLMLQSyaGsYZ2mAeS30GPFAw=", + "lastModified": 1719942255, + "narHash": "sha256-UbNZASD2xUk1S/z7yJ+k41kl523MZQW5t2wtPwemUhM=", "owner": "phadej", - "repo": "gentle-introduction", - "rev": "407fe323ce0633afedabd92efdd968b8e22f3f1b", + "repo": "cabal-extras", + "rev": "67a889582e7ef118f1c26b8f105abd2120f84fd0", "type": "github" }, "original": { "owner": "phadej", - "repo": "gentle-introduction", + "ref": "cabal-docspec-0.0.0.20240703", + "repo": "cabal-extras", "type": "github" } }, - "ghc-8.6.5-iohk": { - "flake": false, + "cardano-automation": { + "inputs": { + "flake-utils": "flake-utils", + "haskellNix": [ + "cardano-nix", + "cardano-node", + "haskellNix" + ], + "nixpkgs": [ + "cardano-nix", + "cardano-node", + "nixpkgs" + ] + }, "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "lastModified": 1741965132, + "narHash": "sha256-SjNEfsLa+2FKS4GlszaH0fO/QGJbooNFMYU1GVdJToo=", "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "repo": "cardano-automation", + "rev": "78d16a837d74a72822041ee1b970daa73ac83b9e", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", + "repo": "cardano-automation", "type": "github" } }, - "hackageNix": { - "flake": false, + "cardano-db-sync": { + "inputs": { + "CHaP": "CHaP_2", + "flake-compat": [ + "cardano-nix", + "flake-compat_" + ], + "hackageNix": [ + "cardano-nix", + "hackageNix_" + ], + "haskellNix": "haskellNix", + "iohkNix": [ + "cardano-nix", + "iohkNix_" + ], + "nixpkgs": [ + "cardano-nix", + "cardano-node", + "nixpkgs" + ], + "nixpkgsUpstream": "nixpkgsUpstream", + "utils": [ + "cardano-nix", + "flake-utils_" + ] + }, "locked": { - "lastModified": 1747268661, - "narHash": "sha256-z+1y/asOg4eOx23SrdMUM2tYhSlBxIFmsx82odczNNk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "232e5cb2402b52c2efd0f58e8ec1e24efcdaa22b", + "lastModified": 1742316958, + "narHash": "sha256-8dADl0Y5mu8rHGADDC56KYV/kQlDFITTpgRiSTHwUc8=", + "owner": "intersectmbo", + "repo": "cardano-db-sync", + "rev": "cb61094c82254464fc9de777225e04d154d9c782", "type": "github" }, "original": { - "owner": "input-output-hk", - "ref": "for-stackage", - "repo": "hackage.nix", + "owner": "intersectmbo", + "ref": "13.6.0.5", + "repo": "cardano-db-sync", "type": "github" } }, - "haskellNix": { + "cardano-nix": { "inputs": { - "HTTP": "HTTP", - "cabal-32": "cabal-32", - "cabal-34": "cabal-34", - "cabal-36": "cabal-36", - "cardano-shell": "cardano-shell", - "flake-compat": "flake-compat_2", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk", - "hackage": [ - "hackageNix" + "blockfrost": "blockfrost", + "cardano-db-sync": "cardano-db-sync", + "cardano-node": "cardano-node", + "crane": "crane", + "crane_": [ + "cardano-nix", + "crane" ], - "hls-1.10": "hls-1.10", - "hls-2.0": "hls-2.0", - "hls-2.2": "hls-2.2", - "hls-2.3": "hls-2.3", - "hls-2.4": "hls-2.4", - "hls-2.5": "hls-2.5", - "hls-2.6": "hls-2.6", - "hls-2.7": "hls-2.7", - "hls-2.8": "hls-2.8", - "hls-2.9": "hls-2.9", - "hpc-coveralls": "hpc-coveralls", - "hydra": "hydra", - "iserv-proxy": "iserv-proxy", + "demeter-run-cli": "demeter-run-cli", + "devour-flake": "devour-flake", + "devshell": "devshell", + "flake-compat_": [ + "cardano-nix", + "cardano-node", + "flake-compat" + ], + "flake-parts": "flake-parts", + "flake-root": "flake-root", + "flake-utils_": [ + "cardano-nix", + "cardano-node", + "utils" + ], + "git-hooks-nix": "git-hooks-nix", + "hackageNix_": [ + "cardano-nix", + "cardano-node", + "hackageNix" + ], + "hercules-ci-effects": "hercules-ci-effects", + "iohkNix_": [ + "cardano-nix", + "cardano-node", + "iohkNix" + ], + "nixpkgs": "nixpkgs_4", + "nixpkgs_": [ + "cardano-nix", + "nixpkgs" + ], + "oura": "oura", + "treefmt-nix": "treefmt-nix" + }, + "locked": { + "lastModified": 1758296791, + "narHash": "sha256-n24MZIYh1iVV2BTYEcC9nKzvMpjl7JTK1LAxU1caMOM=", + "owner": "mlabs-haskell", + "repo": "cardano.nix", + "rev": "658bbc86da1f2dc61faa0316b148d71228975860", + "type": "github" + }, + "original": { + "owner": "mlabs-haskell", + "repo": "cardano.nix", + "type": "github" + } + }, + "cardano-node": { + "inputs": { + "CHaP": "CHaP_3", + "cardano-automation": "cardano-automation", + "customConfig": "customConfig", + "em": "em", + "empty-flake": "empty-flake", + "flake-compat": "flake-compat_2", + "hackageNix": "hackageNix", + "haskellNix": "haskellNix_2", + "incl": "incl", + "iohkNix": "iohkNix", "nixpkgs": [ + "cardano-nix", + "cardano-node", "haskellNix", "nixpkgs-unstable" ], - "nixpkgs-2003": "nixpkgs-2003", - "nixpkgs-2105": "nixpkgs-2105", - "nixpkgs-2111": "nixpkgs-2111", - "nixpkgs-2205": "nixpkgs-2205", - "nixpkgs-2211": "nixpkgs-2211", - "nixpkgs-2305": "nixpkgs-2305", - "nixpkgs-2311": "nixpkgs-2311", - "nixpkgs-2405": "nixpkgs-2405", - "nixpkgs-unstable": "nixpkgs-unstable", - "old-ghc-nix": "old-ghc-nix", - "stackage": "stackage" + "utils": "utils" }, "locked": { - "lastModified": 1723683036, - "narHash": "sha256-pT74TrE+bCaeXhYLYJrZVocwopwwua4qOwN7waUdUpU=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "88aeace47b5e43cb4df5f96e754179293c06f47c", + "lastModified": 1752857436, + "narHash": "sha256-YAAwDfzMMTeEQa0zHin7yo2nMdxONJ983tJ3NrP7K6E=", + "owner": "intersectmbo", + "repo": "cardano-node", + "rev": "ca1ec278070baf4481564a6ba7b4a5b9e3d9f366", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", + "owner": "intersectmbo", + "ref": "10.5.1", + "repo": "cardano-node", "type": "github" } }, - "hls-1.10": { + "cardano-shell": { "flake": false, "locked": { - "lastModified": 1680000865, - "narHash": "sha256-rc7iiUAcrHxwRM/s0ErEsSPxOR3u8t7DvFeWlMycWgo=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "b08691db779f7a35ff322b71e72a12f6e3376fd9", + "lastModified": 1608537748, + "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", + "owner": "input-output-hk", + "repo": "cardano-shell", + "rev": "9392c75087cb9a3d453998f4230930dea3a95725", "type": "github" }, "original": { - "owner": "haskell", - "ref": "1.10.0.0", - "repo": "haskell-language-server", + "owner": "input-output-hk", + "repo": "cardano-shell", "type": "github" } }, - "hls-2.0": { + "cardano-shell_2": { "flake": false, "locked": { - "lastModified": 1687698105, - "narHash": "sha256-OHXlgRzs/kuJH8q7Sxh507H+0Rb8b7VOiPAjcY9sM1k=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "783905f211ac63edf982dd1889c671653327e441", + "lastModified": 1608537748, + "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", + "owner": "input-output-hk", + "repo": "cardano-shell", + "rev": "9392c75087cb9a3d453998f4230930dea3a95725", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.0.0.1", - "repo": "haskell-language-server", + "owner": "input-output-hk", + "repo": "cardano-shell", "type": "github" } }, - "hls-2.2": { + "cardano-shell_3": { "flake": false, "locked": { - "lastModified": 1693064058, - "narHash": "sha256-8DGIyz5GjuCFmohY6Fa79hHA/p1iIqubfJUTGQElbNk=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "b30f4b6cf5822f3112c35d14a0cba51f3fe23b85", + "lastModified": 1608537748, + "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", + "owner": "input-output-hk", + "repo": "cardano-shell", + "rev": "9392c75087cb9a3d453998f4230930dea3a95725", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.2.0.0", - "repo": "haskell-language-server", + "owner": "input-output-hk", + "repo": "cardano-shell", "type": "github" } }, - "hls-2.3": { - "flake": false, + "crane": { "locked": { - "lastModified": 1695910642, - "narHash": "sha256-tR58doOs3DncFehHwCLczJgntyG/zlsSd7DgDgMPOkI=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "458ccdb55c9ea22cd5d13ec3051aaefb295321be", + "lastModified": 1758215636, + "narHash": "sha256-8nkzkPbdxze8CxWhKWlcLbJEU1vfLM/nVqRlTy17V54=", + "owner": "ipetkov", + "repo": "crane", + "rev": "a669fe77a8b0cd6f11419d89ea45a16691ca5121", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.3.0.0", - "repo": "haskell-language-server", + "owner": "ipetkov", + "repo": "crane", "type": "github" } }, - "hls-2.4": { - "flake": false, + "customConfig": { "locked": { - "lastModified": 1699862708, - "narHash": "sha256-YHXSkdz53zd0fYGIYOgLt6HrA0eaRJi9mXVqDgmvrjk=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "54507ef7e85fa8e9d0eb9a669832a3287ffccd57", + "lastModified": 1630400035, + "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", + "owner": "input-output-hk", + "repo": "empty-flake", + "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.4.0.1", - "repo": "haskell-language-server", + "owner": "input-output-hk", + "repo": "empty-flake", "type": "github" } }, - "hls-2.5": { + "demeter-run-cli": { "flake": false, "locked": { - "lastModified": 1701080174, - "narHash": "sha256-fyiR9TaHGJIIR0UmcCb73Xv9TJq3ht2ioxQ2mT7kVdc=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "27f8c3d3892e38edaef5bea3870161815c4d014c", + "lastModified": 1740775656, + "narHash": "sha256-bCyNwn+nmU/wtWvwLig/uFmKlGkjIcpJJgetZJGn3hk=", + "owner": "demeter-run", + "repo": "cli", + "rev": "1b9ef1c4b864dcb22c37b07e9162736b920553eb", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.5.0.0", - "repo": "haskell-language-server", + "owner": "demeter-run", + "repo": "cli", "type": "github" } }, - "hls-2.6": { + "devour-flake": { "flake": false, "locked": { - "lastModified": 1705325287, - "narHash": "sha256-+P87oLdlPyMw8Mgoul7HMWdEvWP/fNlo8jyNtwME8E8=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "6e0b342fa0327e628610f2711f8c3e4eaaa08b1e", + "lastModified": 1738639461, + "narHash": "sha256-R7MHvTh5fskzxNLBe9bher+GQBZ8ZHjz75CPQG3fSRI=", + "owner": "srid", + "repo": "devour-flake", + "rev": "9fe4db872c107ea217c13b24527b68d9e4a4c01b", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.6.0.0", - "repo": "haskell-language-server", + "owner": "srid", + "repo": "devour-flake", "type": "github" } }, - "hls-2.7": { - "flake": false, + "devshell": { + "inputs": { + "nixpkgs": [ + "cardano-nix", + "nixpkgs_" + ] + }, "locked": { - "lastModified": 1708965829, - "narHash": "sha256-LfJ+TBcBFq/XKoiNI7pc4VoHg4WmuzsFxYJ3Fu+Jf+M=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "50322b0a4aefb27adc5ec42f5055aaa8f8e38001", + "lastModified": 1741473158, + "narHash": "sha256-kWNaq6wQUbUMlPgw8Y+9/9wP0F8SHkjy24/mN3UAppg=", + "owner": "numtide", + "repo": "devshell", + "rev": "7c9e793ebe66bcba8292989a68c0419b737a22a0", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.7.0.0", - "repo": "haskell-language-server", + "owner": "numtide", + "repo": "devshell", "type": "github" } }, - "hls-2.8": { + "em": { "flake": false, "locked": { - "lastModified": 1715153580, - "narHash": "sha256-Vi/iUt2pWyUJlo9VrYgTcbRviWE0cFO6rmGi9rmALw0=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "dd1be1beb16700de59e0d6801957290bcf956a0a", + "lastModified": 1685015066, + "narHash": "sha256-etAdEoYhtvjTw1ITh28WPNfwvvb5t/fpwCP6s7odSiQ=", + "owner": "deepfire", + "repo": "em", + "rev": "af69bb5c2ac2161434d8fea45f920f8f359587ce", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.8.0.0", - "repo": "haskell-language-server", + "owner": "deepfire", + "repo": "em", "type": "github" } }, - "hls-2.9": { - "flake": false, + "empty-flake": { "locked": { - "lastModified": 1718469202, - "narHash": "sha256-THXSz+iwB1yQQsr/PY151+2GvtoJnTIB2pIQ4OzfjD4=", - "owner": "haskell", - "repo": "haskell-language-server", - "rev": "40891bccb235ebacce020b598b083eab9dda80f1", + "lastModified": 1630400035, + "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", + "owner": "input-output-hk", + "repo": "empty-flake", + "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", "type": "github" }, "original": { - "owner": "haskell", - "ref": "2.9.0.0", - "repo": "haskell-language-server", + "owner": "input-output-hk", + "repo": "empty-flake", "type": "github" } }, - "hpc-coveralls": { + "flake-compat": { "flake": false, "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", + "lastModified": 1672831974, + "narHash": "sha256-z9k3MfslLjWQfnjBtEtJZdq3H7kyi2kQtUThfTgdRk0=", + "owner": "input-output-hk", + "repo": "flake-compat", + "rev": "45f2638735f8cdc40fe302742b79f248d23eb368", "type": "github" }, "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", + "owner": "input-output-hk", + "ref": "hkm/gitlab-fix", + "repo": "flake-compat", "type": "github" } }, - "hydra": { - "inputs": { - "nix": "nix", - "nixpkgs": [ - "haskellNix", - "hydra", - "nix", - "nixpkgs" - ] - }, + "flake-compat_2": { + "flake": false, "locked": { - "lastModified": 1671755331, - "narHash": "sha256-hXsgJj0Cy0ZiCiYdW2OdBz5WmFyOMKuw4zyxKpgUKm4=", - "owner": "NixOS", - "repo": "hydra", - "rev": "f48f00ee6d5727ae3e488cbf9ce157460853fea8", + "lastModified": 1647532380, + "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "owner": "input-output-hk", + "repo": "flake-compat", + "rev": "7da118186435255a30b5ffeabba9629c344c0bec", "type": "github" }, "original": { - "id": "hydra", - "type": "indirect" + "owner": "input-output-hk", + "ref": "fixes", + "repo": "flake-compat", + "type": "github" } }, - "iohkNix": { - "inputs": { - "blst": "blst", - "nixpkgs": [ - "nixpkgs" - ], - "secp256k1": "secp256k1", - "sodium": "sodium" - }, + "flake-compat_3": { + "flake": false, "locked": { - "lastModified": 1721825987, - "narHash": "sha256-PPcma4tjozwXJAWf+YtHUQUulmxwulVlwSQzKItx/n8=", + "lastModified": 1672831974, + "narHash": "sha256-z9k3MfslLjWQfnjBtEtJZdq3H7kyi2kQtUThfTgdRk0=", "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "eb61f2c14e1f610ec59117ad40f8690cddbf80cb", + "repo": "flake-compat", + "rev": "45f2638735f8cdc40fe302742b79f248d23eb368", "type": "github" }, "original": { "owner": "input-output-hk", - "repo": "iohk-nix", + "ref": "hkm/gitlab-fix", + "repo": "flake-compat", "type": "github" } }, - "iserv-proxy": { + "flake-compat_4": { "flake": false, "locked": { - "lastModified": 1717479972, - "narHash": "sha256-7vE3RQycHI1YT9LHJ1/fUaeln2vIpYm6Mmn8FTpYeVo=", - "owner": "stable-haskell", - "repo": "iserv-proxy", - "rev": "2ed34002247213fc435d0062350b91bab920626e", + "lastModified": 1717312683, + "narHash": "sha256-FrlieJH50AuvagamEvWMIE6D2OAnERuDboFDYAED/dE=", + "owner": "nix-community", + "repo": "flake-compat", + "rev": "38fd3954cf65ce6faf3d0d45cd26059e059f07ea", "type": "github" }, "original": { - "owner": "stable-haskell", - "ref": "iserv-syms", - "repo": "iserv-proxy", + "owner": "nix-community", + "repo": "flake-compat", "type": "github" } }, - "lowdown-src": { + "flake-compat_5": { + "flake": false, + "locked": { + "lastModified": 1672831974, + "narHash": "sha256-z9k3MfslLjWQfnjBtEtJZdq3H7kyi2kQtUThfTgdRk0=", + "owner": "input-output-hk", + "repo": "flake-compat", + "rev": "45f2638735f8cdc40fe302742b79f248d23eb368", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "hkm/gitlab-fix", + "repo": "flake-compat", + "type": "github" + } + }, + "flake-parts": { + "inputs": { + "nixpkgs-lib": [ + "cardano-nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1756770412, + "narHash": "sha256-+uWLQZccFHwqpGqr2Yt5VsW/PbeJVTn9Dk6SHWhNRPw=", + "owner": "hercules-ci", + "repo": "flake-parts", + "rev": "4524271976b625a4a605beefd893f270620fd751", + "type": "github" + }, + "original": { + "owner": "hercules-ci", + "repo": "flake-parts", + "type": "github" + } + }, + "flake-root": { + "locked": { + "lastModified": 1723604017, + "narHash": "sha256-rBtQ8gg+Dn4Sx/s+pvjdq3CB2wQNzx9XGFq/JVGCB6k=", + "owner": "srid", + "repo": "flake-root", + "rev": "b759a56851e10cb13f6b8e5698af7b59c44be26e", + "type": "github" + }, + "original": { + "owner": "srid", + "repo": "flake-root", + "type": "github" + } + }, + "flake-utils": { + "locked": { + "lastModified": 1667395993, + "narHash": "sha256-nuEHfE/LcWyuSWnS8t12N1wc105Qtau+/OdUAjtQ0rA=", + "owner": "numtide", + "repo": "flake-utils", + "rev": "5aed5285a952e0b949eb3ba02c12fa4fcfef535f", + "type": "github" + }, + "original": { + "owner": "numtide", + "repo": "flake-utils", + "type": "github" + } + }, + "flake-utils_2": { + "inputs": { + "systems": "systems_2" + }, + "locked": { + "lastModified": 1710146030, + "narHash": "sha256-SZ5L6eA7HJ/nmkzGG7/ISclqe6oZdOZTNoesiInkXPQ=", + "owner": "numtide", + "repo": "flake-utils", + "rev": "b1d9ab70662946ef0850d488da1c9019f3a9752a", + "type": "github" + }, + "original": { + "owner": "numtide", + "repo": "flake-utils", + "type": "github" + } + }, + "gentle-introduction": { + "flake": false, + "locked": { + "lastModified": 1719935136, + "narHash": "sha256-CJQHzxMyyw62tzkBMbymLMLQSyaGsYZ2mAeS30GPFAw=", + "owner": "phadej", + "repo": "gentle-introduction", + "rev": "407fe323ce0633afedabd92efdd968b8e22f3f1b", + "type": "github" + }, + "original": { + "owner": "phadej", + "repo": "gentle-introduction", + "type": "github" + } + }, + "ghc-8.6.5-iohk": { + "flake": false, + "locked": { + "lastModified": 1600920045, + "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "owner": "input-output-hk", + "repo": "ghc", + "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "release/8.6.5-iohk", + "repo": "ghc", + "type": "github" + } + }, + "ghc-8.6.5-iohk_2": { + "flake": false, + "locked": { + "lastModified": 1600920045, + "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "owner": "input-output-hk", + "repo": "ghc", + "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "release/8.6.5-iohk", + "repo": "ghc", + "type": "github" + } + }, + "ghc-8.6.5-iohk_3": { + "flake": false, + "locked": { + "lastModified": 1600920045, + "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "owner": "input-output-hk", + "repo": "ghc", + "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "release/8.6.5-iohk", + "repo": "ghc", + "type": "github" + } + }, + "ghc910X": { + "flake": false, + "locked": { + "lastModified": 1714520650, + "narHash": "sha256-4uz6RA1hRr0RheGNDM49a/B3jszqNNU8iHIow4mSyso=", + "ref": "ghc-9.10", + "rev": "2c6375b9a804ac7fca1e82eb6fcfc8594c67c5f5", + "revCount": 62663, + "submodules": true, + "type": "git", + "url": "https://gitlab.haskell.org/ghc/ghc" + }, + "original": { + "ref": "ghc-9.10", + "submodules": true, + "type": "git", + "url": "https://gitlab.haskell.org/ghc/ghc" + } + }, + "ghc911": { + "flake": false, + "locked": { + "lastModified": 1714817013, + "narHash": "sha256-m2je4UvWfkgepMeUIiXHMwE6W+iVfUY38VDGkMzjCcc=", + "ref": "refs/heads/master", + "rev": "fc24c5cf6c62ca9e3c8d236656e139676df65034", + "revCount": 62816, + "submodules": true, + "type": "git", + "url": "https://gitlab.haskell.org/ghc/ghc" + }, + "original": { + "submodules": true, + "type": "git", + "url": "https://gitlab.haskell.org/ghc/ghc" + } + }, + "git-hooks-nix": { + "inputs": { + "flake-compat": [ + "cardano-nix", + "flake-compat_" + ], + "gitignore": "gitignore", + "nixpkgs": [ + "cardano-nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1758108966, + "narHash": "sha256-ytw7ROXaWZ7OfwHrQ9xvjpUWeGVm86pwnEd1QhzawIo=", + "owner": "cachix", + "repo": "git-hooks.nix", + "rev": "54df955a695a84cd47d4a43e08e1feaf90b1fd9b", + "type": "github" + }, + "original": { + "owner": "cachix", + "repo": "git-hooks.nix", + "type": "github" + } + }, + "gitignore": { + "inputs": { + "nixpkgs": [ + "cardano-nix", + "git-hooks-nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1709087332, + "narHash": "sha256-HG2cCnktfHsKV0s4XW83gU3F57gaTljL9KNSuG6bnQs=", + "owner": "hercules-ci", + "repo": "gitignore.nix", + "rev": "637db329424fd7e46cf4185293b9cc8c88c95394", + "type": "github" + }, + "original": { + "owner": "hercules-ci", + "repo": "gitignore.nix", + "type": "github" + } + }, + "hackageNix": { + "flake": false, + "locked": { + "lastModified": 1745281520, + "narHash": "sha256-dk/70Cmjx8fGSURcAHQnowETeAOElzDxn0wH/P4DUWA=", + "owner": "input-output-hk", + "repo": "hackage.nix", + "rev": "4c98778277c642e326b3cb7c2c9cbb9163b9ffbd", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "for-stackage", + "repo": "hackage.nix", + "type": "github" + } + }, + "hackageNix_2": { + "flake": false, + "locked": { + "lastModified": 1747268661, + "narHash": "sha256-z+1y/asOg4eOx23SrdMUM2tYhSlBxIFmsx82odczNNk=", + "owner": "input-output-hk", + "repo": "hackage.nix", + "rev": "232e5cb2402b52c2efd0f58e8ec1e24efcdaa22b", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "ref": "for-stackage", + "repo": "hackage.nix", + "type": "github" + } + }, + "haskellNix": { + "inputs": { + "HTTP": "HTTP", + "cabal-32": "cabal-32", + "cabal-34": "cabal-34", + "cabal-36": "cabal-36", + "cardano-shell": "cardano-shell", + "flake-compat": "flake-compat", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk", + "hackage": [ + "cardano-nix", + "cardano-db-sync", + "hackageNix" + ], + "hls-1.10": "hls-1.10", + "hls-2.0": "hls-2.0", + "hls-2.2": "hls-2.2", + "hls-2.3": "hls-2.3", + "hls-2.4": "hls-2.4", + "hls-2.5": "hls-2.5", + "hls-2.6": "hls-2.6", + "hls-2.7": "hls-2.7", + "hls-2.8": "hls-2.8", + "hls-2.9": "hls-2.9", + "hpc-coveralls": "hpc-coveralls", + "hydra": "hydra", + "iserv-proxy": "iserv-proxy", + "nixpkgs": [ + "cardano-nix", + "cardano-db-sync", + "haskellNix", + "nixpkgs-unstable" + ], + "nixpkgs-2003": "nixpkgs-2003", + "nixpkgs-2105": "nixpkgs-2105", + "nixpkgs-2111": "nixpkgs-2111", + "nixpkgs-2205": "nixpkgs-2205", + "nixpkgs-2211": "nixpkgs-2211", + "nixpkgs-2305": "nixpkgs-2305", + "nixpkgs-2311": "nixpkgs-2311", + "nixpkgs-2405": "nixpkgs-2405", + "nixpkgs-unstable": "nixpkgs-unstable", + "old-ghc-nix": "old-ghc-nix", + "stackage": "stackage" + }, + "locked": { + "lastModified": 1729471867, + "narHash": "sha256-xMxD8YQGGcbrZGHJws32UvtWJxfhzAO7yzPs5TjiOPY=", + "owner": "input-output-hk", + "repo": "haskell.nix", + "rev": "03c3581d2e0c91f7c2690115b487961ad62099a6", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "haskell.nix", + "type": "github" + } + }, + "haskellNix_2": { + "inputs": { + "HTTP": "HTTP_2", + "cabal-32": "cabal-32_2", + "cabal-34": "cabal-34_2", + "cabal-36": "cabal-36_2", + "cardano-shell": "cardano-shell_2", + "flake-compat": "flake-compat_3", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_2", + "ghc910X": "ghc910X", + "ghc911": "ghc911", + "hackage": [ + "cardano-nix", + "cardano-node", + "hackageNix" + ], + "hls-1.10": "hls-1.10_2", + "hls-2.0": "hls-2.0_2", + "hls-2.2": "hls-2.2_2", + "hls-2.3": "hls-2.3_2", + "hls-2.4": "hls-2.4_2", + "hls-2.5": "hls-2.5_2", + "hls-2.6": "hls-2.6_2", + "hls-2.7": "hls-2.7_2", + "hls-2.8": "hls-2.8_2", + "hpc-coveralls": "hpc-coveralls_2", + "hydra": "hydra_2", + "iserv-proxy": "iserv-proxy_2", + "nixpkgs": [ + "cardano-nix", + "cardano-node", + "nixpkgs" + ], + "nixpkgs-2003": "nixpkgs-2003_2", + "nixpkgs-2105": "nixpkgs-2105_2", + "nixpkgs-2111": "nixpkgs-2111_2", + "nixpkgs-2205": "nixpkgs-2205_2", + "nixpkgs-2211": "nixpkgs-2211_2", + "nixpkgs-2305": "nixpkgs-2305_2", + "nixpkgs-2311": "nixpkgs-2311_2", + "nixpkgs-unstable": "nixpkgs-unstable_2", + "old-ghc-nix": "old-ghc-nix_2", + "stackage": "stackage_2" + }, + "locked": { + "lastModified": 1718797200, + "narHash": "sha256-ueFxTuZrQ3ZT/Fj5sSeUWlqKa4+OkUU1xW0E+q/XTfw=", + "owner": "input-output-hk", + "repo": "haskell.nix", + "rev": "cb139fa956158397aa398186bb32dd26f7318784", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "haskell.nix", + "rev": "cb139fa956158397aa398186bb32dd26f7318784", + "type": "github" + } + }, + "haskellNix_3": { + "inputs": { + "HTTP": "HTTP_3", + "cabal-32": "cabal-32_3", + "cabal-34": "cabal-34_3", + "cabal-36": "cabal-36_3", + "cardano-shell": "cardano-shell_3", + "flake-compat": "flake-compat_5", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_3", + "hackage": [ + "hackageNix" + ], + "hls-1.10": "hls-1.10_3", + "hls-2.0": "hls-2.0_3", + "hls-2.2": "hls-2.2_3", + "hls-2.3": "hls-2.3_3", + "hls-2.4": "hls-2.4_3", + "hls-2.5": "hls-2.5_3", + "hls-2.6": "hls-2.6_3", + "hls-2.7": "hls-2.7_3", + "hls-2.8": "hls-2.8_3", + "hls-2.9": "hls-2.9_2", + "hpc-coveralls": "hpc-coveralls_3", + "hydra": "hydra_3", + "iserv-proxy": "iserv-proxy_3", + "nixpkgs": [ + "haskellNix", + "nixpkgs-unstable" + ], + "nixpkgs-2003": "nixpkgs-2003_3", + "nixpkgs-2105": "nixpkgs-2105_3", + "nixpkgs-2111": "nixpkgs-2111_3", + "nixpkgs-2205": "nixpkgs-2205_3", + "nixpkgs-2211": "nixpkgs-2211_3", + "nixpkgs-2305": "nixpkgs-2305_3", + "nixpkgs-2311": "nixpkgs-2311_3", + "nixpkgs-2405": "nixpkgs-2405_2", + "nixpkgs-unstable": "nixpkgs-unstable_3", + "old-ghc-nix": "old-ghc-nix_3", + "stackage": "stackage_3" + }, + "locked": { + "lastModified": 1723683036, + "narHash": "sha256-pT74TrE+bCaeXhYLYJrZVocwopwwua4qOwN7waUdUpU=", + "owner": "input-output-hk", + "repo": "haskell.nix", + "rev": "88aeace47b5e43cb4df5f96e754179293c06f47c", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "haskell.nix", + "type": "github" + } + }, + "hercules-ci-effects": { + "inputs": { + "flake-parts": [ + "cardano-nix", + "flake-parts" + ], + "nixpkgs": [ + "cardano-nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1714676393, + "narHash": "sha256-OA2LZPTCHyH0PcsNkjeTLvgsn4JmsV2VTvXQacHeUZU=", + "owner": "mlabs-haskell", + "repo": "hercules-ci-effects", + "rev": "5ad8f9613b735cb4f8222f07ae45ca37bfe76a23", + "type": "github" + }, + "original": { + "owner": "mlabs-haskell", + "ref": "push-cache-effect", + "repo": "hercules-ci-effects", + "type": "github" + } + }, + "hls-1.10": { + "flake": false, + "locked": { + "lastModified": 1680000865, + "narHash": "sha256-rc7iiUAcrHxwRM/s0ErEsSPxOR3u8t7DvFeWlMycWgo=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b08691db779f7a35ff322b71e72a12f6e3376fd9", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "1.10.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-1.10_2": { + "flake": false, + "locked": { + "lastModified": 1680000865, + "narHash": "sha256-rc7iiUAcrHxwRM/s0ErEsSPxOR3u8t7DvFeWlMycWgo=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b08691db779f7a35ff322b71e72a12f6e3376fd9", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "1.10.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-1.10_3": { + "flake": false, + "locked": { + "lastModified": 1680000865, + "narHash": "sha256-rc7iiUAcrHxwRM/s0ErEsSPxOR3u8t7DvFeWlMycWgo=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b08691db779f7a35ff322b71e72a12f6e3376fd9", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "1.10.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.0": { + "flake": false, + "locked": { + "lastModified": 1687698105, + "narHash": "sha256-OHXlgRzs/kuJH8q7Sxh507H+0Rb8b7VOiPAjcY9sM1k=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "783905f211ac63edf982dd1889c671653327e441", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.0.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.0_2": { + "flake": false, + "locked": { + "lastModified": 1687698105, + "narHash": "sha256-OHXlgRzs/kuJH8q7Sxh507H+0Rb8b7VOiPAjcY9sM1k=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "783905f211ac63edf982dd1889c671653327e441", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.0.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.0_3": { + "flake": false, + "locked": { + "lastModified": 1687698105, + "narHash": "sha256-OHXlgRzs/kuJH8q7Sxh507H+0Rb8b7VOiPAjcY9sM1k=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "783905f211ac63edf982dd1889c671653327e441", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.0.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.2": { + "flake": false, + "locked": { + "lastModified": 1693064058, + "narHash": "sha256-8DGIyz5GjuCFmohY6Fa79hHA/p1iIqubfJUTGQElbNk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b30f4b6cf5822f3112c35d14a0cba51f3fe23b85", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.2.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.2_2": { + "flake": false, + "locked": { + "lastModified": 1693064058, + "narHash": "sha256-8DGIyz5GjuCFmohY6Fa79hHA/p1iIqubfJUTGQElbNk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b30f4b6cf5822f3112c35d14a0cba51f3fe23b85", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.2.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.2_3": { + "flake": false, + "locked": { + "lastModified": 1693064058, + "narHash": "sha256-8DGIyz5GjuCFmohY6Fa79hHA/p1iIqubfJUTGQElbNk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "b30f4b6cf5822f3112c35d14a0cba51f3fe23b85", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.2.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.3": { + "flake": false, + "locked": { + "lastModified": 1695910642, + "narHash": "sha256-tR58doOs3DncFehHwCLczJgntyG/zlsSd7DgDgMPOkI=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "458ccdb55c9ea22cd5d13ec3051aaefb295321be", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.3.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.3_2": { + "flake": false, + "locked": { + "lastModified": 1695910642, + "narHash": "sha256-tR58doOs3DncFehHwCLczJgntyG/zlsSd7DgDgMPOkI=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "458ccdb55c9ea22cd5d13ec3051aaefb295321be", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.3.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.3_3": { + "flake": false, + "locked": { + "lastModified": 1695910642, + "narHash": "sha256-tR58doOs3DncFehHwCLczJgntyG/zlsSd7DgDgMPOkI=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "458ccdb55c9ea22cd5d13ec3051aaefb295321be", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.3.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.4": { + "flake": false, + "locked": { + "lastModified": 1699862708, + "narHash": "sha256-YHXSkdz53zd0fYGIYOgLt6HrA0eaRJi9mXVqDgmvrjk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "54507ef7e85fa8e9d0eb9a669832a3287ffccd57", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.4.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.4_2": { + "flake": false, + "locked": { + "lastModified": 1699862708, + "narHash": "sha256-YHXSkdz53zd0fYGIYOgLt6HrA0eaRJi9mXVqDgmvrjk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "54507ef7e85fa8e9d0eb9a669832a3287ffccd57", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.4.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.4_3": { + "flake": false, + "locked": { + "lastModified": 1699862708, + "narHash": "sha256-YHXSkdz53zd0fYGIYOgLt6HrA0eaRJi9mXVqDgmvrjk=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "54507ef7e85fa8e9d0eb9a669832a3287ffccd57", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.4.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.5": { + "flake": false, + "locked": { + "lastModified": 1701080174, + "narHash": "sha256-fyiR9TaHGJIIR0UmcCb73Xv9TJq3ht2ioxQ2mT7kVdc=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "27f8c3d3892e38edaef5bea3870161815c4d014c", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.5.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.5_2": { + "flake": false, + "locked": { + "lastModified": 1701080174, + "narHash": "sha256-fyiR9TaHGJIIR0UmcCb73Xv9TJq3ht2ioxQ2mT7kVdc=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "27f8c3d3892e38edaef5bea3870161815c4d014c", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.5.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.5_3": { + "flake": false, + "locked": { + "lastModified": 1701080174, + "narHash": "sha256-fyiR9TaHGJIIR0UmcCb73Xv9TJq3ht2ioxQ2mT7kVdc=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "27f8c3d3892e38edaef5bea3870161815c4d014c", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.5.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.6": { + "flake": false, + "locked": { + "lastModified": 1705325287, + "narHash": "sha256-+P87oLdlPyMw8Mgoul7HMWdEvWP/fNlo8jyNtwME8E8=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "6e0b342fa0327e628610f2711f8c3e4eaaa08b1e", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.6.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.6_2": { + "flake": false, + "locked": { + "lastModified": 1705325287, + "narHash": "sha256-+P87oLdlPyMw8Mgoul7HMWdEvWP/fNlo8jyNtwME8E8=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "6e0b342fa0327e628610f2711f8c3e4eaaa08b1e", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.6.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.6_3": { + "flake": false, + "locked": { + "lastModified": 1705325287, + "narHash": "sha256-+P87oLdlPyMw8Mgoul7HMWdEvWP/fNlo8jyNtwME8E8=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "6e0b342fa0327e628610f2711f8c3e4eaaa08b1e", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.6.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.7": { + "flake": false, + "locked": { + "lastModified": 1708965829, + "narHash": "sha256-LfJ+TBcBFq/XKoiNI7pc4VoHg4WmuzsFxYJ3Fu+Jf+M=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "50322b0a4aefb27adc5ec42f5055aaa8f8e38001", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.7.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.7_2": { + "flake": false, + "locked": { + "lastModified": 1708965829, + "narHash": "sha256-LfJ+TBcBFq/XKoiNI7pc4VoHg4WmuzsFxYJ3Fu+Jf+M=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "50322b0a4aefb27adc5ec42f5055aaa8f8e38001", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.7.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.7_3": { + "flake": false, + "locked": { + "lastModified": 1708965829, + "narHash": "sha256-LfJ+TBcBFq/XKoiNI7pc4VoHg4WmuzsFxYJ3Fu+Jf+M=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "50322b0a4aefb27adc5ec42f5055aaa8f8e38001", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.7.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.8": { + "flake": false, + "locked": { + "lastModified": 1715153580, + "narHash": "sha256-Vi/iUt2pWyUJlo9VrYgTcbRviWE0cFO6rmGi9rmALw0=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "dd1be1beb16700de59e0d6801957290bcf956a0a", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.8.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.8_2": { + "flake": false, + "locked": { + "lastModified": 1715153580, + "narHash": "sha256-Vi/iUt2pWyUJlo9VrYgTcbRviWE0cFO6rmGi9rmALw0=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "dd1be1beb16700de59e0d6801957290bcf956a0a", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.8.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.8_3": { + "flake": false, + "locked": { + "lastModified": 1715153580, + "narHash": "sha256-Vi/iUt2pWyUJlo9VrYgTcbRviWE0cFO6rmGi9rmALw0=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "dd1be1beb16700de59e0d6801957290bcf956a0a", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.8.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.9": { + "flake": false, + "locked": { + "lastModified": 1720003792, + "narHash": "sha256-qnDx8Pk0UxtoPr7BimEsAZh9g2WuTuMB/kGqnmdryKs=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "0c1817cb2babef0765e4e72dd297c013e8e3d12b", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.9.0.1", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hls-2.9_2": { + "flake": false, + "locked": { + "lastModified": 1718469202, + "narHash": "sha256-THXSz+iwB1yQQsr/PY151+2GvtoJnTIB2pIQ4OzfjD4=", + "owner": "haskell", + "repo": "haskell-language-server", + "rev": "40891bccb235ebacce020b598b083eab9dda80f1", + "type": "github" + }, + "original": { + "owner": "haskell", + "ref": "2.9.0.0", + "repo": "haskell-language-server", + "type": "github" + } + }, + "hpc-coveralls": { + "flake": false, + "locked": { + "lastModified": 1607498076, + "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", + "type": "github" + }, + "original": { + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "type": "github" + } + }, + "hpc-coveralls_2": { + "flake": false, + "locked": { + "lastModified": 1607498076, + "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", + "type": "github" + }, + "original": { + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "type": "github" + } + }, + "hpc-coveralls_3": { + "flake": false, + "locked": { + "lastModified": 1607498076, + "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", + "type": "github" + }, + "original": { + "owner": "sevanspowell", + "repo": "hpc-coveralls", + "type": "github" + } + }, + "hydra": { + "inputs": { + "nix": "nix", + "nixpkgs": [ + "cardano-nix", + "cardano-db-sync", + "haskellNix", + "hydra", + "nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1671755331, + "narHash": "sha256-hXsgJj0Cy0ZiCiYdW2OdBz5WmFyOMKuw4zyxKpgUKm4=", + "owner": "NixOS", + "repo": "hydra", + "rev": "f48f00ee6d5727ae3e488cbf9ce157460853fea8", + "type": "github" + }, + "original": { + "id": "hydra", + "type": "indirect" + } + }, + "hydra_2": { + "inputs": { + "nix": "nix_2", + "nixpkgs": [ + "cardano-nix", + "cardano-node", + "haskellNix", + "hydra", + "nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1671755331, + "narHash": "sha256-hXsgJj0Cy0ZiCiYdW2OdBz5WmFyOMKuw4zyxKpgUKm4=", + "owner": "NixOS", + "repo": "hydra", + "rev": "f48f00ee6d5727ae3e488cbf9ce157460853fea8", + "type": "github" + }, + "original": { + "id": "hydra", + "type": "indirect" + } + }, + "hydra_3": { + "inputs": { + "nix": "nix_3", + "nixpkgs": [ + "haskellNix", + "hydra", + "nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1671755331, + "narHash": "sha256-hXsgJj0Cy0ZiCiYdW2OdBz5WmFyOMKuw4zyxKpgUKm4=", + "owner": "NixOS", + "repo": "hydra", + "rev": "f48f00ee6d5727ae3e488cbf9ce157460853fea8", + "type": "github" + }, + "original": { + "id": "hydra", + "type": "indirect" + } + }, + "incl": { + "inputs": { + "nixlib": "nixlib" + }, + "locked": { + "lastModified": 1693483555, + "narHash": "sha256-Beq4WhSeH3jRTZgC1XopTSU10yLpK1nmMcnGoXO0XYo=", + "owner": "divnix", + "repo": "incl", + "rev": "526751ad3d1e23b07944b14e3f6b7a5948d3007b", + "type": "github" + }, + "original": { + "owner": "divnix", + "repo": "incl", + "type": "github" + } + }, + "iohkNix": { + "inputs": { + "blst": "blst", + "nixpkgs": [ + "cardano-nix", + "cardano-node", + "nixpkgs" + ], + "secp256k1": "secp256k1", + "sodium": "sodium" + }, + "locked": { + "lastModified": 1750025513, + "narHash": "sha256-WUNoYIZvU9moc5ccwJcF22r+bUJXO5dWoRyLPs8bJic=", + "owner": "input-output-hk", + "repo": "iohk-nix", + "rev": "f63aa2a49720526900fb5943db4123b5b8dcc534", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "iohk-nix", + "type": "github" + } + }, + "iohkNix_2": { + "inputs": { + "blst": "blst_2", + "nixpkgs": [ + "nixpkgs" + ], + "secp256k1": "secp256k1_2", + "sodium": "sodium_2" + }, + "locked": { + "lastModified": 1721825987, + "narHash": "sha256-PPcma4tjozwXJAWf+YtHUQUulmxwulVlwSQzKItx/n8=", + "owner": "input-output-hk", + "repo": "iohk-nix", + "rev": "eb61f2c14e1f610ec59117ad40f8690cddbf80cb", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "iohk-nix", + "type": "github" + } + }, + "iserv-proxy": { + "flake": false, + "locked": { + "lastModified": 1717479972, + "narHash": "sha256-7vE3RQycHI1YT9LHJ1/fUaeln2vIpYm6Mmn8FTpYeVo=", + "owner": "stable-haskell", + "repo": "iserv-proxy", + "rev": "2ed34002247213fc435d0062350b91bab920626e", + "type": "github" + }, + "original": { + "owner": "stable-haskell", + "ref": "iserv-syms", + "repo": "iserv-proxy", + "type": "github" + } + }, + "iserv-proxy_2": { + "flake": false, + "locked": { + "lastModified": 1717479972, + "narHash": "sha256-7vE3RQycHI1YT9LHJ1/fUaeln2vIpYm6Mmn8FTpYeVo=", + "owner": "stable-haskell", + "repo": "iserv-proxy", + "rev": "2ed34002247213fc435d0062350b91bab920626e", + "type": "github" + }, + "original": { + "owner": "stable-haskell", + "ref": "iserv-syms", + "repo": "iserv-proxy", + "type": "github" + } + }, + "iserv-proxy_3": { + "flake": false, + "locked": { + "lastModified": 1717479972, + "narHash": "sha256-7vE3RQycHI1YT9LHJ1/fUaeln2vIpYm6Mmn8FTpYeVo=", + "owner": "stable-haskell", + "repo": "iserv-proxy", + "rev": "2ed34002247213fc435d0062350b91bab920626e", + "type": "github" + }, + "original": { + "owner": "stable-haskell", + "ref": "iserv-syms", + "repo": "iserv-proxy", + "type": "github" + } + }, + "lowdown-src": { + "flake": false, + "locked": { + "lastModified": 1633514407, + "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", + "owner": "kristapsdz", + "repo": "lowdown", + "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", + "type": "github" + }, + "original": { + "owner": "kristapsdz", + "repo": "lowdown", + "type": "github" + } + }, + "lowdown-src_2": { + "flake": false, + "locked": { + "lastModified": 1633514407, + "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", + "owner": "kristapsdz", + "repo": "lowdown", + "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", + "type": "github" + }, + "original": { + "owner": "kristapsdz", + "repo": "lowdown", + "type": "github" + } + }, + "lowdown-src_3": { "flake": false, "locked": { "lastModified": 1633514407, @@ -566,204 +1976,645 @@ "type": "github" }, "original": { - "owner": "kristapsdz", - "repo": "lowdown", + "owner": "kristapsdz", + "repo": "lowdown", + "type": "github" + } + }, + "nix": { + "inputs": { + "lowdown-src": "lowdown-src", + "nixpkgs": "nixpkgs_2", + "nixpkgs-regression": "nixpkgs-regression" + }, + "locked": { + "lastModified": 1661606874, + "narHash": "sha256-9+rpYzI+SmxJn+EbYxjGv68Ucp22bdFUSy/4LkHkkDQ=", + "owner": "NixOS", + "repo": "nix", + "rev": "11e45768b34fdafdcf019ddbd337afa16127ff0f", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "2.11.0", + "repo": "nix", + "type": "github" + } + }, + "nix_2": { + "inputs": { + "lowdown-src": "lowdown-src_2", + "nixpkgs": "nixpkgs_3", + "nixpkgs-regression": "nixpkgs-regression_2" + }, + "locked": { + "lastModified": 1661606874, + "narHash": "sha256-9+rpYzI+SmxJn+EbYxjGv68Ucp22bdFUSy/4LkHkkDQ=", + "owner": "NixOS", + "repo": "nix", + "rev": "11e45768b34fdafdcf019ddbd337afa16127ff0f", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "2.11.0", + "repo": "nix", + "type": "github" + } + }, + "nix_3": { + "inputs": { + "lowdown-src": "lowdown-src_3", + "nixpkgs": "nixpkgs_5", + "nixpkgs-regression": "nixpkgs-regression_3" + }, + "locked": { + "lastModified": 1661606874, + "narHash": "sha256-9+rpYzI+SmxJn+EbYxjGv68Ucp22bdFUSy/4LkHkkDQ=", + "owner": "NixOS", + "repo": "nix", + "rev": "11e45768b34fdafdcf019ddbd337afa16127ff0f", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "2.11.0", + "repo": "nix", + "type": "github" + } + }, + "nixlib": { + "locked": { + "lastModified": 1667696192, + "narHash": "sha256-hOdbIhnpWvtmVynKcsj10nxz9WROjZja+1wRAJ/C9+s=", + "owner": "nix-community", + "repo": "nixpkgs.lib", + "rev": "babd9cd2ca6e413372ed59fbb1ecc3c3a5fd3e5b", + "type": "github" + }, + "original": { + "owner": "nix-community", + "repo": "nixpkgs.lib", + "type": "github" + } + }, + "nixpkgs": { + "locked": { + "lastModified": 1687420147, + "narHash": "sha256-NILbmZVsoP2Aw0OAIXdbYXrWc/qggIDDyIwZ01yUx+Q=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "d449a456ba7d81038fc9ec9141eae7ee3aaf2982", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "release-23.05", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2003": { + "locked": { + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-20.03-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2003_2": { + "locked": { + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-20.03-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2003_3": { + "locked": { + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-20.03-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2105": { + "locked": { + "lastModified": 1659914493, + "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2105_2": { + "locked": { + "lastModified": 1659914493, + "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2105_3": { + "locked": { + "lastModified": 1659914493, + "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2111": { + "locked": { + "lastModified": 1659446231, + "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2111_2": { + "locked": { + "lastModified": 1659446231, + "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2111_3": { + "locked": { + "lastModified": 1659446231, + "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-21.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2205": { + "locked": { + "lastModified": 1685573264, + "narHash": "sha256-Zffu01pONhs/pqH07cjlF10NnMDLok8ix5Uk4rhOnZQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "380be19fbd2d9079f677978361792cb25e8a3635", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2205_2": { + "locked": { + "lastModified": 1685573264, + "narHash": "sha256-Zffu01pONhs/pqH07cjlF10NnMDLok8ix5Uk4rhOnZQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "380be19fbd2d9079f677978361792cb25e8a3635", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2205_3": { + "locked": { + "lastModified": 1685573264, + "narHash": "sha256-Zffu01pONhs/pqH07cjlF10NnMDLok8ix5Uk4rhOnZQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "380be19fbd2d9079f677978361792cb25e8a3635", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2211": { + "locked": { + "lastModified": 1688392541, + "narHash": "sha256-lHrKvEkCPTUO+7tPfjIcb7Trk6k31rz18vkyqmkeJfY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "ea4c80b39be4c09702b0cb3b42eab59e2ba4f24b", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2211_2": { + "locked": { + "lastModified": 1688392541, + "narHash": "sha256-lHrKvEkCPTUO+7tPfjIcb7Trk6k31rz18vkyqmkeJfY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "ea4c80b39be4c09702b0cb3b42eab59e2ba4f24b", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2211_3": { + "locked": { + "lastModified": 1688392541, + "narHash": "sha256-lHrKvEkCPTUO+7tPfjIcb7Trk6k31rz18vkyqmkeJfY=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "ea4c80b39be4c09702b0cb3b42eab59e2ba4f24b", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-22.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2305": { + "locked": { + "lastModified": 1705033721, + "narHash": "sha256-K5eJHmL1/kev6WuqyqqbS1cdNnSidIZ3jeqJ7GbrYnQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "a1982c92d8980a0114372973cbdfe0a307f1bdea", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2305_2": { + "locked": { + "lastModified": 1701362232, + "narHash": "sha256-GVdzxL0lhEadqs3hfRLuj+L1OJFGiL/L7gCcelgBlsw=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "d2332963662edffacfddfad59ff4f709dde80ffe", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2305_3": { + "locked": { + "lastModified": 1705033721, + "narHash": "sha256-K5eJHmL1/kev6WuqyqqbS1cdNnSidIZ3jeqJ7GbrYnQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "a1982c92d8980a0114372973cbdfe0a307f1bdea", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.05-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2311": { + "locked": { + "lastModified": 1719957072, + "narHash": "sha256-gvFhEf5nszouwLAkT9nWsDzocUTqLWHuL++dvNjMp9I=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "7144d6241f02d171d25fba3edeaf15e0f2592105", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2311_2": { + "locked": { + "lastModified": 1701386440, + "narHash": "sha256-xI0uQ9E7JbmEy/v8kR9ZQan6389rHug+zOtZeZFiDJk=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "293822e55ec1872f715a66d0eda9e592dc14419f", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2311_3": { + "locked": { + "lastModified": 1719957072, + "narHash": "sha256-gvFhEf5nszouwLAkT9nWsDzocUTqLWHuL++dvNjMp9I=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "7144d6241f02d171d25fba3edeaf15e0f2592105", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-23.11-darwin", + "repo": "nixpkgs", + "type": "github" + } + }, + "nixpkgs-2405": { + "locked": { + "lastModified": 1726447378, + "narHash": "sha256-2yV8nmYE1p9lfmLHhOCbYwQC/W8WYfGQABoGzJOb1JQ=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "086b448a5d54fd117f4dc2dee55c9f0ff461bdc1", + "type": "github" + }, + "original": { + "owner": "NixOS", + "ref": "nixpkgs-24.05-darwin", + "repo": "nixpkgs", "type": "github" } }, - "nix": { - "inputs": { - "lowdown-src": "lowdown-src", - "nixpkgs": "nixpkgs", - "nixpkgs-regression": "nixpkgs-regression" - }, + "nixpkgs-2405_2": { "locked": { - "lastModified": 1661606874, - "narHash": "sha256-9+rpYzI+SmxJn+EbYxjGv68Ucp22bdFUSy/4LkHkkDQ=", + "lastModified": 1720122915, + "narHash": "sha256-Nby8WWxj0elBu1xuRaUcRjPi/rU3xVbkAt2kj4QwX2U=", "owner": "NixOS", - "repo": "nix", - "rev": "11e45768b34fdafdcf019ddbd337afa16127ff0f", + "repo": "nixpkgs", + "rev": "835cf2d3f37989c5db6585a28de967a667a75fb1", "type": "github" }, "original": { "owner": "NixOS", - "ref": "2.11.0", - "repo": "nix", + "ref": "nixpkgs-24.05-darwin", + "repo": "nixpkgs", "type": "github" } }, - "nixpkgs": { + "nixpkgs-regression": { "locked": { - "lastModified": 1657693803, - "narHash": "sha256-G++2CJ9u0E7NNTAi9n5G8TdDmGJXcIjkJ3NF8cetQB8=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "365e1b3a859281cf11b94f87231adeabbdd878a2", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixos-22.05-small", "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" } }, - "nixpkgs-2003": { + "nixpkgs-regression_2": { "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" } }, - "nixpkgs-2105": { + "nixpkgs-regression_3": { "locked": { - "lastModified": 1659914493, - "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" } }, - "nixpkgs-2111": { + "nixpkgs-unstable": { "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "lastModified": 1726583932, + "narHash": "sha256-zACxiQx8knB3F8+Ze+1BpiYrI+CbhxyWpcSID9kVhkQ=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "rev": "658e7223191d2598641d50ee4e898126768fe847", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", + "ref": "nixpkgs-unstable", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2205": { + "nixpkgs-unstable_2": { "locked": { - "lastModified": 1685573264, - "narHash": "sha256-Zffu01pONhs/pqH07cjlF10NnMDLok8ix5Uk4rhOnZQ=", + "lastModified": 1694822471, + "narHash": "sha256-6fSDCj++lZVMZlyqOe9SIOL8tYSBz1bI8acwovRwoX8=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "380be19fbd2d9079f677978361792cb25e8a3635", + "rev": "47585496bcb13fb72e4a90daeea2f434e2501998", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-22.05-darwin", "repo": "nixpkgs", + "rev": "47585496bcb13fb72e4a90daeea2f434e2501998", "type": "github" } }, - "nixpkgs-2211": { + "nixpkgs-unstable_3": { "locked": { - "lastModified": 1688392541, - "narHash": "sha256-lHrKvEkCPTUO+7tPfjIcb7Trk6k31rz18vkyqmkeJfY=", + "lastModified": 1720181791, + "narHash": "sha256-i4vJL12/AdyuQuviMMd1Hk2tsGt02hDNhA0Zj1m16N8=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "ea4c80b39be4c09702b0cb3b42eab59e2ba4f24b", + "rev": "4284c2b73c8bce4b46a6adf23e16d9e2ec8da4bb", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-22.11-darwin", + "ref": "nixpkgs-unstable", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2305": { + "nixpkgsUpstream": { "locked": { - "lastModified": 1705033721, - "narHash": "sha256-K5eJHmL1/kev6WuqyqqbS1cdNnSidIZ3jeqJ7GbrYnQ=", + "lastModified": 1737942377, + "narHash": "sha256-8Eo/jRAgT3CbAloyqOj6uPN1EqBvLI/Tv2g+RxHjkhU=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "a1982c92d8980a0114372973cbdfe0a307f1bdea", + "rev": "88a55dffa4d44d294c74c298daf75824dc0aafb5", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-23.05-darwin", + "ref": "nixpkgs-unstable", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2311": { + "nixpkgs_2": { "locked": { - "lastModified": 1719957072, - "narHash": "sha256-gvFhEf5nszouwLAkT9nWsDzocUTqLWHuL++dvNjMp9I=", + "lastModified": 1657693803, + "narHash": "sha256-G++2CJ9u0E7NNTAi9n5G8TdDmGJXcIjkJ3NF8cetQB8=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "7144d6241f02d171d25fba3edeaf15e0f2592105", + "rev": "365e1b3a859281cf11b94f87231adeabbdd878a2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-23.11-darwin", + "ref": "nixos-22.05-small", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2405": { + "nixpkgs_3": { "locked": { - "lastModified": 1720122915, - "narHash": "sha256-Nby8WWxj0elBu1xuRaUcRjPi/rU3xVbkAt2kj4QwX2U=", + "lastModified": 1657693803, + "narHash": "sha256-G++2CJ9u0E7NNTAi9n5G8TdDmGJXcIjkJ3NF8cetQB8=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "835cf2d3f37989c5db6585a28de967a667a75fb1", + "rev": "365e1b3a859281cf11b94f87231adeabbdd878a2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-24.05-darwin", + "ref": "nixos-22.05-small", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-regression": { + "nixpkgs_4": { "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", + "lastModified": 1758035966, + "narHash": "sha256-qqIJ3yxPiB0ZQTT9//nFGQYn8X/PBoJbofA7hRKZnmE=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "rev": "8d4ddb19d03c65a36ad8d189d001dc32ffb0306b", "type": "github" }, "original": { "owner": "NixOS", + "ref": "nixos-unstable", "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" } }, - "nixpkgs-unstable": { + "nixpkgs_5": { "locked": { - "lastModified": 1720181791, - "narHash": "sha256-i4vJL12/AdyuQuviMMd1Hk2tsGt02hDNhA0Zj1m16N8=", + "lastModified": 1657693803, + "narHash": "sha256-G++2CJ9u0E7NNTAi9n5G8TdDmGJXcIjkJ3NF8cetQB8=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "4284c2b73c8bce4b46a6adf23e16d9e2ec8da4bb", + "rev": "365e1b3a859281cf11b94f87231adeabbdd878a2", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-unstable", + "ref": "nixos-22.05-small", "repo": "nixpkgs", "type": "github" } @@ -785,17 +2636,78 @@ "type": "github" } }, + "old-ghc-nix_2": { + "flake": false, + "locked": { + "lastModified": 1631092763, + "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", + "owner": "angerman", + "repo": "old-ghc-nix", + "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", + "type": "github" + }, + "original": { + "owner": "angerman", + "ref": "master", + "repo": "old-ghc-nix", + "type": "github" + } + }, + "old-ghc-nix_3": { + "flake": false, + "locked": { + "lastModified": 1631092763, + "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", + "owner": "angerman", + "repo": "old-ghc-nix", + "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", + "type": "github" + }, + "original": { + "owner": "angerman", + "ref": "master", + "repo": "old-ghc-nix", + "type": "github" + } + }, + "oura": { + "inputs": { + "crane": [ + "cardano-nix", + "crane_" + ], + "utils": [ + "cardano-nix", + "flake-utils_" + ] + }, + "locked": { + "lastModified": 1750697545, + "narHash": "sha256-M41AcSWxY9tQLkY8+aFo3xvjVo9YaKdnkHhXcc0BqU0=", + "owner": "txpipe", + "repo": "oura", + "rev": "0ea451908aa02e15443d8e40b956094bd0fa22b0", + "type": "github" + }, + "original": { + "owner": "txpipe", + "ref": "v1.9.4", + "repo": "oura", + "type": "github" + } + }, "root": { "inputs": { "CHaP": "CHaP", "agda-nixpkgs": "agda-nixpkgs", "cabal-extras": "cabal-extras", - "flake-compat": "flake-compat", - "flake-utils": "flake-utils", + "cardano-nix": "cardano-nix", + "flake-compat": "flake-compat_4", + "flake-utils": "flake-utils_2", "gentle-introduction": "gentle-introduction", - "hackageNix": "hackageNix", - "haskellNix": "haskellNix", - "iohkNix": "iohkNix", + "hackageNix": "hackageNix_2", + "haskellNix": "haskellNix_3", + "iohkNix": "iohkNix_2", "nixpkgs": [ "haskellNix", "nixpkgs-unstable" @@ -819,6 +2731,23 @@ "type": "github" } }, + "secp256k1_2": { + "flake": false, + "locked": { + "lastModified": 1683999695, + "narHash": "sha256-9nJJVENMXjXEJZzw8DHzin1DkFkF8h9m/c6PuM7Uk4s=", + "owner": "bitcoin-core", + "repo": "secp256k1", + "rev": "acf5c55ae6a94e5ca847e07def40427547876101", + "type": "github" + }, + "original": { + "owner": "bitcoin-core", + "ref": "v0.3.2", + "repo": "secp256k1", + "type": "github" + } + }, "sodium": { "flake": false, "locked": { @@ -836,7 +2765,56 @@ "type": "github" } }, + "sodium_2": { + "flake": false, + "locked": { + "lastModified": 1675156279, + "narHash": "sha256-0uRcN5gvMwO7MCXVYnoqG/OmeBFi8qRVnDWJLnBb9+Y=", + "owner": "input-output-hk", + "repo": "libsodium", + "rev": "dbb48cce5429cb6585c9034f002568964f1ce567", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "libsodium", + "rev": "dbb48cce5429cb6585c9034f002568964f1ce567", + "type": "github" + } + }, "stackage": { + "flake": false, + "locked": { + "lastModified": 1729039017, + "narHash": "sha256-fGExfgG+7UNSOV8YfOrWPpOHWrCjA02gQkeSBhaAzjQ=", + "owner": "input-output-hk", + "repo": "stackage.nix", + "rev": "df1d8f0960407551fea7af7af75a9c2f9e18de97", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "stackage.nix", + "type": "github" + } + }, + "stackage_2": { + "flake": false, + "locked": { + "lastModified": 1718756571, + "narHash": "sha256-8rL8viTbuE9/yV1of6SWp2tHmhVMD2UmkOfmN5KDbKg=", + "owner": "input-output-hk", + "repo": "stackage.nix", + "rev": "027672fb6fd45828b0e623c8152572d4058429ad", + "type": "github" + }, + "original": { + "owner": "input-output-hk", + "repo": "stackage.nix", + "type": "github" + } + }, + "stackage_3": { "flake": false, "locked": { "lastModified": 1723594352, @@ -866,6 +2844,60 @@ "repo": "default", "type": "github" } + }, + "systems_2": { + "locked": { + "lastModified": 1681028828, + "narHash": "sha256-Vy1rq5AaRuLzOxct8nz4T6wlgyUR7zLU309k9mBC768=", + "owner": "nix-systems", + "repo": "default", + "rev": "da67096a3b9bf56a91d16901293e51ba5b49a27e", + "type": "github" + }, + "original": { + "owner": "nix-systems", + "repo": "default", + "type": "github" + } + }, + "treefmt-nix": { + "inputs": { + "nixpkgs": [ + "cardano-nix", + "nixpkgs" + ] + }, + "locked": { + "lastModified": 1758206697, + "narHash": "sha256-/DbPkh6PZOgfueCbs3uzlk4ASU2nPPsiVWhpMCNkAd0=", + "owner": "numtide", + "repo": "treefmt-nix", + "rev": "128222dc911b8e2e18939537bed1762b7f3a04aa", + "type": "github" + }, + "original": { + "owner": "numtide", + "repo": "treefmt-nix", + "type": "github" + } + }, + "utils": { + "inputs": { + "systems": "systems" + }, + "locked": { + "lastModified": 1710146030, + "narHash": "sha256-SZ5L6eA7HJ/nmkzGG7/ISclqe6oZdOZTNoesiInkXPQ=", + "owner": "numtide", + "repo": "flake-utils", + "rev": "b1d9ab70662946ef0850d488da1c9019f3a9752a", + "type": "github" + }, + "original": { + "owner": "numtide", + "repo": "flake-utils", + "type": "github" + } } }, "root": "root", diff --git a/flake.nix b/flake.nix index 948778cda4..e2157af61a 100644 --- a/flake.nix +++ b/flake.nix @@ -41,6 +41,7 @@ url = "github:phadej/gentle-introduction"; flake = false; }; + cardano-nix.url = "github:mlabs-haskell/cardano.nix"; }; outputs = inputs: let @@ -87,7 +88,9 @@ inherit hydraJobs; legacyPackages = pkgs; packages = - hydraJobs.native.haskell96.exesNoAsserts.ouroboros-consensus-cardano; + hydraJobs.native.haskell96.exesNoAsserts.ouroboros-consensus-cardano // { + leios-mvd-test = pkgs.testers.nixosTest (import ./nix/leios-mvd/test.nix {inherit inputs pkgs;}); + }; } ); } diff --git a/nix/leios-mvd/genesis/genesis.alonzo.json b/nix/leios-mvd/genesis/genesis.alonzo.json new file mode 100644 index 0000000000..e13bd102bf --- /dev/null +++ b/nix/leios-mvd/genesis/genesis.alonzo.json @@ -0,0 +1,188 @@ +{ + "collateralPercentage": 150, + "costModels": { + "PlutusV1": [ + 197209, + 0, + 1, + 1, + 396231, + 621, + 0, + 1, + 150000, + 1000, + 0, + 1, + 150000, + 32, + 2477736, + 29175, + 4, + 29773, + 100, + 29773, + 100, + 29773, + 100, + 29773, + 100, + 29773, + 100, + 29773, + 100, + 100, + 100, + 29773, + 100, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 1000, + 0, + 1, + 150000, + 32, + 150000, + 1000, + 0, + 8, + 148000, + 425507, + 118, + 0, + 1, + 1, + 150000, + 1000, + 0, + 8, + 150000, + 112536, + 247, + 1, + 150000, + 10000, + 1, + 136542, + 1326, + 1, + 1000, + 150000, + 1000, + 1, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 1, + 1, + 150000, + 1, + 150000, + 4, + 103599, + 248, + 1, + 103599, + 248, + 1, + 145276, + 1366, + 1, + 179690, + 497, + 1, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 148000, + 425507, + 118, + 0, + 1, + 1, + 61516, + 11218, + 0, + 1, + 150000, + 32, + 148000, + 425507, + 118, + 0, + 1, + 1, + 148000, + 425507, + 118, + 0, + 1, + 1, + 2477736, + 29175, + 4, + 0, + 82363, + 4, + 150000, + 5000, + 0, + 1, + 150000, + 32, + 197209, + 0, + 1, + 1, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 150000, + 32, + 3345831, + 1, + 1 + ] + }, + "executionPrices": { + "priceMemory": 0.0577, + "priceSteps": 0.0000721 + }, + "lovelacePerUTxOWord": 34482, + "maxBlockExUnits": { + "memory": 62000000, + "steps": 20000000000 + }, + "maxCollateralInputs": 3, + "maxTxExUnits": { + "memory": 14000000, + "steps": 10000000000 + }, + "maxValueSize": 5000 +} diff --git a/nix/leios-mvd/genesis/genesis.byron.json b/nix/leios-mvd/genesis/genesis.byron.json new file mode 100644 index 0000000000..db3d32595d --- /dev/null +++ b/nix/leios-mvd/genesis/genesis.byron.json @@ -0,0 +1,42 @@ +{ "bootStakeholders": + { "a8f4fd08e2935ea584899dc306084595c4b9df394ea20dd855236a9d": 1 } +, "heavyDelegation": + { "a8f4fd08e2935ea584899dc306084595c4b9df394ea20dd855236a9d": + { "omega": 0 + , "issuerPk": + "JW5mw+Zo7XnJpBlqMnsrd+cfElAY8AFAWbQuF0+CqTQYgBz9eXza/EiY9sxugu/b6FwJW5fxe3rY83U7VFzEfg==" + , "delegatePk": + "zMajaA9h8Q6gUQ+y6VKHoj4Y1VBjlJyyS0v2eZn67RgNBOK63uxBdut6/1/kLaNMk+MuWB131W/abDCPs8b9og==" + , "cert": + "b12dd4d4d8c87a9af25fa6d5ee78a620573a6712fbeebfc45951d00bf4200a70cb6d4733cfddea576c4fd399e2fd6e2fd60d55f243bc6c8177ed599d699d6d06" + } } +, "startTime": 1759952614 +, "nonAvvmBalances": + { "2657WMsDfac5QzGGBef3oj7pwz4VwHCmNhkhLmN1SSs47qypuS7XQwFNCRVWansbi": + "30000" + , "2657WMsDfac6t6LUFkmDj8GCgJwUxNAPLMnionk3PbkLzVYHAiS7CpMGYUQjjhZQi": + "270000" + } +, "blockVersionData": + { "scriptVersion": 0 + , "slotDuration": "20000" + , "maxBlockSize": "641000" + , "maxHeaderSize": "200000" + , "maxTxSize": "4096" + , "maxProposalSize": "700" + , "mpcThd": "200000" + , "heavyDelThd": "300000" + , "updateVoteThd": "100000" + , "updateProposalThd": "100000" + , "updateImplicit": "10000" + , "softforkRule": + { "initThd": "900000" + , "minThd": "600000" + , "thdDecrement": "100000" + } + , "txFeePolicy": { "summand": "0" , "multiplier": "439460" } + , "unlockStakeEpoch": "184467" + } +, "protocolConsts": { "k": 2160 , "protocolMagic": 42 } +, "avvmDistr": {} +} \ No newline at end of file diff --git a/nix/leios-mvd/genesis/genesis.conway.json b/nix/leios-mvd/genesis/genesis.conway.json new file mode 100644 index 0000000000..70f8103f31 --- /dev/null +++ b/nix/leios-mvd/genesis/genesis.conway.json @@ -0,0 +1,337 @@ +{ + "committee": { + "members": {}, + "threshold": 0 + }, + "committeeMaxTermLength": 146, + "committeeMinSize": 7, + "constitution": { + "anchor": { + "dataHash": "0000000000000000000000000000000000000000000000000000000000000000", + "url": "" + } + }, + "dRepActivity": 20, + "dRepDeposit": 500000000, + "dRepVotingThresholds": { + "committeeNoConfidence": 0.6, + "committeeNormal": 0.67, + "hardForkInitiation": 0.6, + "motionNoConfidence": 0.67, + "ppEconomicGroup": 0.67, + "ppGovGroup": 0.75, + "ppNetworkGroup": 0.67, + "ppTechnicalGroup": 0.67, + "treasuryWithdrawal": 0.67, + "updateToConstitution": 0.75 + }, + "govActionDeposit": 100000000000, + "govActionLifetime": 6, + "minFeeRefScriptCostPerByte": 15, + "plutusV3CostModel": [ + 100788, + 420, + 1, + 1, + 1000, + 173, + 0, + 1, + 1000, + 59957, + 4, + 1, + 11183, + 32, + 201305, + 8356, + 4, + 16000, + 100, + 16000, + 100, + 16000, + 100, + 16000, + 100, + 16000, + 100, + 16000, + 100, + 100, + 100, + 16000, + 100, + 94375, + 32, + 132994, + 32, + 61462, + 4, + 72010, + 178, + 0, + 1, + 22151, + 32, + 91189, + 769, + 4, + 2, + 85848, + 123203, + 7305, + -900, + 1716, + 549, + 57, + 85848, + 0, + 1, + 1, + 1000, + 42921, + 4, + 2, + 24548, + 29498, + 38, + 1, + 898148, + 27279, + 1, + 51775, + 558, + 1, + 39184, + 1000, + 60594, + 1, + 141895, + 32, + 83150, + 32, + 15299, + 32, + 76049, + 1, + 13169, + 4, + 22100, + 10, + 28999, + 74, + 1, + 28999, + 74, + 1, + 43285, + 552, + 1, + 44749, + 541, + 1, + 33852, + 32, + 68246, + 32, + 72362, + 32, + 7243, + 32, + 7391, + 32, + 11546, + 32, + 85848, + 123203, + 7305, + -900, + 1716, + 549, + 57, + 85848, + 0, + 1, + 90434, + 519, + 0, + 1, + 74433, + 32, + 85848, + 123203, + 7305, + -900, + 1716, + 549, + 57, + 85848, + 0, + 1, + 1, + 85848, + 123203, + 7305, + -900, + 1716, + 549, + 57, + 85848, + 0, + 1, + 955506, + 213312, + 0, + 2, + 270652, + 22588, + 4, + 1457325, + 64566, + 4, + 20467, + 1, + 4, + 0, + 141992, + 32, + 100788, + 420, + 1, + 1, + 81663, + 32, + 59498, + 32, + 20142, + 32, + 24588, + 32, + 20744, + 32, + 25933, + 32, + 24623, + 32, + 43053543, + 10, + 53384111, + 14333, + 10, + 43574283, + 26308, + 10, + 16000, + 100, + 16000, + 100, + 962335, + 18, + 2780678, + 6, + 442008, + 1, + 52538055, + 3756, + 18, + 267929, + 18, + 76433006, + 8868, + 18, + 52948122, + 18, + 1995836, + 36, + 3227919, + 12, + 901022, + 1, + 166917843, + 4307, + 36, + 284546, + 36, + 158221314, + 26549, + 36, + 74698472, + 36, + 333849714, + 1, + 254006273, + 72, + 2174038, + 72, + 2261318, + 64571, + 4, + 207616, + 8310, + 4, + 1293828, + 28716, + 63, + 0, + 1, + 1006041, + 43623, + 251, + 0, + 1, + 100181, + 726, + 719, + 0, + 1, + 100181, + 726, + 719, + 0, + 1, + 100181, + 726, + 719, + 0, + 1, + 107878, + 680, + 0, + 1, + 95336, + 1, + 281145, + 18848, + 0, + 1, + 180194, + 159, + 1, + 1, + 158519, + 8942, + 0, + 1, + 159378, + 8813, + 0, + 1, + 107490, + 3298, + 1, + 106057, + 655, + 1, + 1964219, + 24520, + 3 + ], + "poolVotingThresholds": { + "committeeNoConfidence": 0.51, + "committeeNormal": 0.51, + "hardForkInitiation": 0.51, + "motionNoConfidence": 0.51, + "ppSecurityGroup": 0.51 + } +} diff --git a/nix/leios-mvd/genesis/genesis.shelley.json b/nix/leios-mvd/genesis/genesis.shelley.json new file mode 100644 index 0000000000..cd07b300b1 --- /dev/null +++ b/nix/leios-mvd/genesis/genesis.shelley.json @@ -0,0 +1,97 @@ +{ + "activeSlotsCoeff": 0.050, + "epochLength": 600, + "genDelegs": {}, + "initialFunds": { + "00635eef9a08f327a0ce009466914e8f607cebf76e9f4c9f92b0a829f4eab4c172777c708cd0bcac1a16d41b513e3a0f3dff8d182c2878947c": 900000000000000, + "00f00bb672d5d2f064707e6c955234da597e9b43ed6e458a3d15870a8257ef7aac3c0f6e4fbc3e253e3f4e58039986e89492c02c812e703d69": 900000000000000, + "601c6db4e8b6b36e265b9eecba0cb9a653cdd8701f708beccd911f838b": 9000000000000 + }, + "maxKESEvolutions": 62, + "maxLovelaceSupply": 2010000000000000, + "networkId": "Testnet", + "networkMagic": 42, + "protocolParams": { + "a0": 0.3, + "decentralisationParam": 0, + "eMax": 18, + "extraEntropy": { + "tag": "NeutralNonce" + }, + "keyDeposit": 2000000, + "maxBlockBodySize": 90112, + "maxBlockHeaderSize": 1100, + "maxTxSize": 16384, + "minFeeA": 44, + "minFeeB": 155381, + "minPoolCost": 340000000, + "minUTxOValue": 0, + "nOpt": 500, + "poolDeposit": 500000000, + "protocolVersion": { + "major": 10, + "minor": 0 + }, + "rho": 0.0030, + "tau": 0.2 + }, + "securityParam": 3, + "slotLength": 1, + "slotsPerKESPeriod": 129600, + "staking": { + "pools": { + "4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7": { + "cost": 0, + "margin": 0, + "metadata": null, + "owners": [], + "pledge": 0, + "publicKey": "4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7", + "relays": [ + { + "single host name": { + "dnsName": "node-0", + "port": 30000 + } + } + ], + "rewardAccount": { + "credential": { + "keyHash": "48d482deb658ae1aaa522a365e68f9747da98015500e1c260dca3c73" + }, + "network": "Testnet" + }, + "vrf": "03670fa208cb10b3452f04be890c931e4f34eff777dec589f1631d66c971c40c" + }, + "68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc": { + "cost": 0, + "margin": 0, + "metadata": null, + "owners": [], + "pledge": 0, + "publicKey": "68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc", + "relays": [ + { + "single host name": { + "dnsName": "node-1", + "port": 30001 + } + } + ], + "rewardAccount": { + "credential": { + "keyHash": "df587edcea6b53ed8bdc416be16f00beaaef18b5c6b25294275bf117" + }, + "network": "Testnet" + }, + "vrf": "0a570d439272a91eca089a9d04d9a94f11bb86c8daa3991fa67b35468049d60e" + } + }, + "stake": { + "57ef7aac3c0f6e4fbc3e253e3f4e58039986e89492c02c812e703d69": "4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7", + "eab4c172777c708cd0bcac1a16d41b513e3a0f3dff8d182c2878947c": "68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc" + } + }, + "systemStart": "2025-10-08T19:43:34Z", + "updateQuorum": 5 +} diff --git a/nix/leios-mvd/leios-node/config.json b/nix/leios-mvd/leios-node/config.json new file mode 100644 index 0000000000..8380aa5fb0 --- /dev/null +++ b/nix/leios-mvd/leios-node/config.json @@ -0,0 +1,279 @@ +{ + "AlonzoGenesisFile": "genesis-alonzo.json", + "ByronGenesisFile": "genesis-byron.json", + "ConwayGenesisFile": "genesis-conway.json", + "ShelleyGenesisFile": "genesis-shelley.json", + "ChainSyncIdleTimeout": 0, + "EnableP2P": true, + "ExperimentalHardForksEnabled": true, + "ExperimentalProtocolsEnabled": true, + "LastKnownBlockVersion-Alt": 0, + "LastKnownBlockVersion-Major": 3, + "LastKnownBlockVersion-Minor": 0, + "PeerSharing": false, + "Protocol": "Cardano", + "RequiresNetworkMagic": "RequiresMagic", + "SnapshotInterval": 4230, + "SyncTargetNumberOfActivePeers": 15, + "SyncTargetNumberOfEstablishedPeers": 40, + "TargetNumberOfActivePeers": 15, + "TargetNumberOfEstablishedPeers": 40, + "TestAllegraHardForkAtEpoch": 0, + "TestAlonzoHardForkAtEpoch": 0, + "TestBabbageHardForkAtEpoch": 0, + "TestConwayHardForkAtEpoch": 0, + "TestMaryHardForkAtEpoch": 0, + "TestShelleyHardForkAtEpoch": 0, + "TraceOptionForwarder": { + "connQueueSize": 64, + "disconnQueueSize": 128, + "maxReconnectDelay": 30 + }, + "TraceOptionMetricsPrefix": "cardano.node.metrics.", + "TraceOptionNodeName": "leios-node", + "TraceOptionPeerFrequency": 2000, + "TraceOptionResourceFrequency": 1000, + "TraceOptions": { + "": { + "backends": [ + "Stdout MachineFormat", + "EKGBackend", + "Forwarder" + ], + "detail": "DNormal", + "severity": "Notice" + }, + "BlockFetch.Client": { + "severity": "Debug" + }, + "BlockFetch.Client.CompletedBlockFetch": { + "maxFrequency": 2.0 + }, + "BlockFetch.Decision": { + "severity": "Notice" + }, + "BlockFetch.Remote": { + "severity": "Notice" + }, + "BlockFetch.Remote.Serialised": { + "severity": "Notice" + }, + "BlockFetch.Server": { + "severity": "Debug" + }, + "BlockchainTime": { + "severity": "Notice" + }, + "ChainDB": { + "severity": "Debug" + }, + "ChainDB.AddBlockEvent.AddBlockValidation": { + "severity": "Silence" + }, + "ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate": { + "maxFrequency": 2.0 + }, + "ChainDB.AddBlockEvent.AddedBlockToQueue": { + "maxFrequency": 2.0 + }, + "ChainDB.AddBlockEvent.AddedBlockToVolatileDB": { + "maxFrequency": 2.0 + }, + "ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB": { + "maxFrequency": 2.0 + }, + "ChainDB.LedgerEvent.Flavor.V1.OnDisk.BackingStoreEvent": { + "severity": "Silence" + }, + "ChainDB.LedgerEvent.Forker": { + "severity": "Silence" + }, + "ChainDB.ReplayBlock.LedgerReplay": { + "severity": "Notice" + }, + "ChainSync.Client": { + "severity": "Debug" + }, + "ChainSync.Local": { + "severity": "Notice" + }, + "ChainSync.Remote": { + "severity": "Notice" + }, + "ChainSync.Remote.Serialised": { + "severity": "Notice" + }, + "ChainSync.ServerBlock": { + "severity": "Notice" + }, + "ChainSync.ServerHeader": { + "severity": "Debug" + }, + "Consensus.GSM": { + "severity": "Info" + }, + "Forge.Loop": { + "severity": "Debug" + }, + "Forge.StateInfo": { + "severity": "Debug" + }, + "LedgerMetrics": { + "severity": "Info" + }, + "Mempool": { + "severity": "Debug" + }, + "Mempool.AttemptAdd": { + "severity": "Silence" + }, + "Mempool.LedgerFound": { + "severity": "Silence" + }, + "Mempool.LedgerNotFound": { + "severity": "Silence" + }, + "Mempool.SyncNotNeeded": { + "severity": "Silence" + }, + "Mempool.Synced": { + "severity": "Silence" + }, + "Net": { + "severity": "Notice" + }, + "Net.AcceptPolicy": { + "severity": "Debug" + }, + "Net.ConnectionManager.Local": { + "severity": "Debug" + }, + "Net.ConnectionManager.Remote": { + "severity": "Debug" + }, + "Net.ConnectionManager.Remote.ConnectionManagerCounters": { + "severity": "Silence" + }, + "Net.DNSResolver": { + "severity": "Notice" + }, + "Net.ErrorPolicy": { + "severity": "Info" + }, + "Net.ErrorPolicy.Local": { + "severity": "Debug" + }, + "Net.ErrorPolicy.Remote": { + "severity": "Debug" + }, + "Net.Handshake.Local": { + "severity": "Debug" + }, + "Net.Handshake.Remote": { + "severity": "Debug" + }, + "Net.InboundGovernor": { + "severity": "Warning" + }, + "Net.InboundGovernor.Local": { + "severity": "Debug" + }, + "Net.InboundGovernor.Remote": { + "severity": "Debug" + }, + "Net.InboundGovernor.Transition": { + "severity": "Debug" + }, + "Net.Mux.Local": { + "severity": "Notice" + }, + "Net.Mux.Remote": { + "severity": "Notice" + }, + "Net.PeerSelection": { + "severity": "Silence" + }, + "Net.PeerSelection.Actions": { + "severity": "Debug" + }, + "Net.PeerSelection.Counters": { + "detail": "DMinimal", + "severity": "Debug" + }, + "Net.PeerSelection.Initiator": { + "severity": "Notice" + }, + "Net.PeerSelection.Responder": { + "severity": "Notice" + }, + "Net.PeerSelection.Selection": { + "severity": "Debug" + }, + "Net.Peers.Ledger": { + "severity": "Debug" + }, + "Net.Peers.List": { + "severity": "Notice" + }, + "Net.Peers.LocalRoot": { + "severity": "Debug" + }, + "Net.Peers.PublicRoot": { + "severity": "Debug" + }, + "Net.Server.Local": { + "severity": "Debug" + }, + "Net.Server.Remote": { + "severity": "Debug" + }, + "Net.Subscription.DNS": { + "severity": "Debug" + }, + "Net.Subscription.IP": { + "severity": "Debug" + }, + "NodeState": { + "severity": "Notice" + }, + "Resources": { + "severity": "Debug" + }, + "Shutdown": { + "severity": "Notice" + }, + "Startup": { + "severity": "Notice" + }, + "Startup.DiffusionInit": { + "severity": "Debug" + }, + "StateQueryServer": { + "severity": "Notice" + }, + "TxSubmission.Local": { + "severity": "Notice" + }, + "TxSubmission.LocalServer": { + "severity": "Notice" + }, + "TxSubmission.MonitorClient": { + "severity": "Notice" + }, + "TxSubmission.Remote": { + "severity": "Notice" + }, + "TxSubmission.TxInbound": { + "severity": "Debug" + }, + "TxSubmission.TxOutbound": { + "severity": "Notice" + }, + "Version.NodeVersion": { + "severity": "Info" + } + }, + "TurnOnLogMetrics": true, + "TurnOnLogging": true, + "UseTraceDispatcher": true +} diff --git a/nix/leios-mvd/leios-node/delegate.key b/nix/leios-mvd/leios-node/delegate.key new file mode 100644 index 0000000000..b9deddfbc3 --- /dev/null +++ b/nix/leios-mvd/leios-node/delegate.key @@ -0,0 +1 @@ +X€à°+~‚u[~¼vsIï ×Ê5Lï¸r¿°PáÈMVK°¤Mµot‡ !œð;[ªàNý[ýÓ#÷LÿÃסeÌÆ£hañ Q²éR‡¢>ÕPc”œ²KKöy™úí âºÞìAvëzÿ_ä-£L“ã.XwÕoÚl0³Æý¢ \ No newline at end of file diff --git a/nix/leios-mvd/leios-node/delegation-cert.json b/nix/leios-mvd/leios-node/delegation-cert.json new file mode 100644 index 0000000000..b76371e83b --- /dev/null +++ b/nix/leios-mvd/leios-node/delegation-cert.json @@ -0,0 +1,8 @@ +{ "omega": 0 +, "issuerPk": + "JW5mw+Zo7XnJpBlqMnsrd+cfElAY8AFAWbQuF0+CqTQYgBz9eXza/EiY9sxugu/b6FwJW5fxe3rY83U7VFzEfg==" +, "delegatePk": + "zMajaA9h8Q6gUQ+y6VKHoj4Y1VBjlJyyS0v2eZn67RgNBOK63uxBdut6/1/kLaNMk+MuWB131W/abDCPs8b9og==" +, "cert": + "b12dd4d4d8c87a9af25fa6d5ee78a620573a6712fbeebfc45951d00bf4200a70cb6d4733cfddea576c4fd399e2fd6e2fd60d55f243bc6c8177ed599d699d6d06" +} \ No newline at end of file diff --git a/nix/leios-mvd/leios-node/kes.skey b/nix/leios-mvd/leios-node/kes.skey new file mode 100755 index 0000000000..92f1c55ec5 --- /dev/null +++ b/nix/leios-mvd/leios-node/kes.skey @@ -0,0 +1,5 @@ +{ + "type": "KesSigningKey_ed25519_kes_2^6", + "description": "KES Signing Key", + "cborHex": "590260011faaf560676abd9c02c262a77040b224d5196ac05a4f21ee11b25ecc312efbac8a39fecde32833653ba0f1a0bf52ec00eba4829baa6502e33c105008ef014e698b666bb24f2560234a567cb616debc47da8aa0f1581eae5eb856074246097f03f4bed1947c66d1879cadde323a6e1db4e3531b2ff31cf7f3c18c448d51d45c31ba4dc912b198464d75b1ff9641f95d38d00050c55a35026bb09339e80acecf0e2f75dbee68eca3b0b61490331b43ace53656a651b67fbe044e0955cdba7164f92a06d98b36400c5202ac42bff07fb4f6ccccfb84c0d388699cbe2293fc9461be34f439971e7a7cb8fa671528c536d05e0c265c20e4a9a9b543d16e543abaa32fa06489eaaa9373103d9fa459fe7d30e97278759ca46ae9e255737008f0931e3f9c5fba1857769da5d294a8cd4655f7d439edb7a174b09c1609017994dcddb46b0d9c2f156eb28ebd58ec290a36868ec0935108acae6fc11b4127b1619d1310e05603a28969958f2995c5cbdc45b8d95188885079e4d9bd0c7f08fa80edf1cceb851ee037dfebb80277336fc254aa9b0d42cedf53cd6a8fc312071fd8eba8dd0527e39dde8593653d64efc23fef04549f7606c07f6bce1d5d41aa46f4d57e48cfb2c7eda5fcc41254155f739e00ee763c29dbdd19b8d1e95110999693179f3e0f9ec71edc46576768f81e11c7feddef75de2656b3f1245711a166b6f4671ef4c0e60993cde87be49bbeab378db5ac844783c5baaabb26f62d1e14d9f7a2ce9c5608ac133eb356f5e865fb5cbb3ec879a0e8a747e4bdc62a78e72e8f79d197052ba6f11a005791177cd75836adffec022f16178ddd70b52fbd9d66f277b9a31a" +} diff --git a/nix/leios-mvd/leios-node/kes.vkey b/nix/leios-mvd/leios-node/kes.vkey new file mode 100644 index 0000000000..80d1cc9a3c --- /dev/null +++ b/nix/leios-mvd/leios-node/kes.vkey @@ -0,0 +1,5 @@ +{ + "type": "KesVerificationKey_ed25519_kes_2^6", + "description": "KES Verification Key", + "cborHex": "5820dc7d3718e179dcf42925b3f000582bd1d5b590fe4828bbf5b7725885dd0b6716" +} diff --git a/nix/leios-mvd/leios-node/opcert b/nix/leios-mvd/leios-node/opcert new file mode 100644 index 0000000000..1ba028131c --- /dev/null +++ b/nix/leios-mvd/leios-node/opcert @@ -0,0 +1,5 @@ +{ + "type": "NodeOperationalCertificate", + "description": "", + "cborHex": "82845820dc7d3718e179dcf42925b3f000582bd1d5b590fe4828bbf5b7725885dd0b67160000584010d761a13b5609068d8d852d4cf83de4c3d20272e1234fea74c46657c60a59b01ad6fe8fb92d833338351423f0cb9a361636831393127fb63e5c6f2ab1a3bf0b58206b134e73ed0cd24f68c8a0ed08fd24dddfbcaa364563af3480a527f749752cb9" +} diff --git a/nix/leios-mvd/leios-node/os.nix b/nix/leios-mvd/leios-node/os.nix new file mode 100644 index 0000000000..f5e9786500 --- /dev/null +++ b/nix/leios-mvd/leios-node/os.nix @@ -0,0 +1,25 @@ +{inputs, ...}:{ + imports = [ + inputs.cardano-nix.nixosModules.default + ]; + cardano = { + networkNumber = 42; + private-testnet-node = { + enable = true; + nodeConfigFile = ./config.json; + + genesisAlonzo = ../genesis/genesis.alonzo.json; + genesisConway = ../genesis/genesis.conway.json; + genesisShelley = ../genesis/genesis.shelley.json; + genesisByron = ../genesis/genesis.byron.json; + + topology = ./topology.json; + + vrfKey = ./vrf.skey; + kesKey = ./kes.skey; + operationalCertificate = ./opcert; + delegationCertificate = ./delegation-cert.json; + signingKey = ./delegate.key; + }; + }; +} diff --git a/nix/leios-mvd/leios-node/topology.json b/nix/leios-mvd/leios-node/topology.json new file mode 100644 index 0000000000..f478b45075 --- /dev/null +++ b/nix/leios-mvd/leios-node/topology.json @@ -0,0 +1,18 @@ +{ + "bootstrapPeers": null, + "localRoots": [ + { + "accessPoints": [ + { + "address": "immdb-node", + "port": 30001 + } + ], + "advertise": false, + "trustable": true, + "valency": 1 + } + ], + "publicRoots": [], + "useLedgerAfterSlot": -1 +} diff --git a/nix/leios-mvd/leios-node/vrf.skey b/nix/leios-mvd/leios-node/vrf.skey new file mode 100755 index 0000000000..2f45bf176a --- /dev/null +++ b/nix/leios-mvd/leios-node/vrf.skey @@ -0,0 +1,5 @@ +{ + "type": "VrfSigningKey_PraosVRF", + "description": "VRF Signing Key", + "cborHex": "58409c0a6066829b1979048d611268dbffb49633738f3ba542fb90279a1b789fdcf9ad1b97904ad19d7083a217f2385e891189fe054641e52880d5d1d680aa453898" +} diff --git a/nix/leios-mvd/leios-node/vrf.vkey b/nix/leios-mvd/leios-node/vrf.vkey new file mode 100644 index 0000000000..1110d66588 --- /dev/null +++ b/nix/leios-mvd/leios-node/vrf.vkey @@ -0,0 +1,5 @@ +{ + "type": "VrfVerificationKey_PraosVRF", + "description": "VRF Verification Key", + "cborHex": "5820ad1b97904ad19d7083a217f2385e891189fe054641e52880d5d1d680aa453898" +} diff --git a/nix/leios-mvd/test.nix b/nix/leios-mvd/test.nix new file mode 100644 index 0000000000..221ced1845 --- /dev/null +++ b/nix/leios-mvd/test.nix @@ -0,0 +1,14 @@ +{inputs, pkgs, ...}: +{ + name = "Leios MVD NixOS test"; + + nodes = { + leios-node = import ./leios-node/os.nix {inherit inputs;}; + }; + + testScript = '' + start_all() + + leios_node.wait_for_unit("cardano-node.service") + ''; +} From cbdd85ab4dfd868f38c8b3ffb525a43cb577a871 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 14 Oct 2025 16:04:46 +0200 Subject: [PATCH 011/119] Git ignore NixOS test history files and direnv --- .gitignore | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index 5c88fe9214..723b2c5f1f 100644 --- a/.gitignore +++ b/.gitignore @@ -100,3 +100,5 @@ cabal.project.local cabal.project.local~ .HTF/ .ghc.environment.* +.nixos-test-history +.direnv/ \ No newline at end of file From 231a2a1fb4a17069265e329ae6c18fd122e007ad Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 06:49:05 -0700 Subject: [PATCH 012/119] leiosdemo202510: avoid reversing long lists --- ouroboros-consensus/app/leiosdemo202510.hs | 36 ++++++++++------------ 1 file changed, 16 insertions(+), 20 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index d608a8bca2..87adb02caa 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -280,37 +280,31 @@ encodeEB bytesToLen hashToBytes ebItems = -- -- The @[a]@ is less than 1024 long. -- --- Each 'V.Vector' is exactly 1024. -data X a = X [V.Vector a] !Word16 [a] +-- Each 'V.Vector' is exactly 1024 long. +data X a = X !Word16 [a] [V.Vector a] + deriving (Functor, Foldable) emptyX :: X a -emptyX = X [] 0 [] - -pushX :: a -> X a -> X a -pushX x (X vs n xs) = - if n < 1024 then X vs (n+1) (x : xs) else - X (V.fromList (reverse xs) : vs) 1 [x] - --- | helper for msgLeiosBlockRequest -newtype Y a = Y [V.Vector a] - deriving (Functor, Foldable) +emptyX = X 0 [] [] -finalizeX :: X a -> Y a -finalizeX (X vs _n xs) = Y $ reverse $ V.fromList (reverse xs) : vs +pushX :: X a -> a -> X a +pushX (X n xs vs) x = + if n < 1024 then X (n+1) (x : xs) vs else + X 1 [x] (V.fromList xs : vs) msgLeiosBlockRequest :: DB.Database -> Word64 -> ByteString -> IO () msgLeiosBlockRequest db ebSlot ebHash = do -- get the EB items - stmt_lookup_ebBodies <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies) + stmt_lookup_ebBodies <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) withDie $ DB.bindInt64 stmt_lookup_ebBodies 1 (fromIntegral ebSlot) withDie $ DB.bindBlob stmt_lookup_ebBodies 2 ebHash let loop !acc = do withDie (DB.stepNoCB stmt_lookup_ebBodies) >>= \case - DB.Done -> pure $ finalizeX acc + DB.Done -> pure acc DB.Row -> do txHash <- DB.columnBlob stmt_lookup_ebBodies 0 txSizeInBytes <- DB.columnInt64 stmt_lookup_ebBodies 1 - loop $ pushX (txSizeInBytes, txHash) acc + loop $ pushX acc (txSizeInBytes, txHash) y <- loop emptyX -- combine the EB items BS.putStr @@ -319,12 +313,14 @@ msgLeiosBlockRequest db ebSlot ebHash = do $ encodeEB fromIntegral id y putStrLn "" -sql_lookup_ebBodies :: String -sql_lookup_ebBodies = +-- | It's DESCending because the accumulator within the 'msgLeiosBlockRequest' +-- logic naturally reverses it +sql_lookup_ebBodies_DESC :: String +sql_lookup_ebBodies_DESC = "SELECT ebBodies.txHash, ebBodies.txSizeInBytes FROM ebBodies\n\ \INNER JOIN ebPoints ON ebBodies.ebPoint = ebPoints.id\n\ \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ?\n\ - \ORDER BY ebBodies.txOffset\n\ + \ORDER BY ebBodies.txOffset DESC\n\ \" msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () From 7efc564d205ca7348fbd245788b84bea438d1310 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 10:31:33 -0700 Subject: [PATCH 013/119] leiosdemo202510: fallback for requests of many txs --- ouroboros-consensus/app/leiosdemo202510.hs | 70 ++++++++++++++++------ 1 file changed, 51 insertions(+), 19 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 87adb02caa..3becf98d95 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -302,6 +302,7 @@ msgLeiosBlockRequest db ebSlot ebHash = do withDie (DB.stepNoCB stmt_lookup_ebBodies) >>= \case DB.Done -> pure acc DB.Row -> do + -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? txHash <- DB.columnBlob stmt_lookup_ebBodies 0 txSizeInBytes <- DB.columnInt64 stmt_lookup_ebBodies 1 loop $ pushX acc (txSizeInBytes, txHash) @@ -325,11 +326,16 @@ sql_lookup_ebBodies_DESC = msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do - when (not $ let idxs = map fst bitmaps in and $ zipWith (<) idxs (tail idxs)) $ do - die "Offsets not strictly ascending" - when (1000 < sum (map (Bits.popCount . snd) bitmaps)) $ do - -- TODO insert into temp table and join? - die "Too many offsets in one request" + do + let idxs = map fst bitmaps + let maxEbByteSize = 12500000 :: Int + minTxByteSize = 55 + idxLimit = (maxEbByteSize `div` minTxByteSize) `div` 64 + when (flip any idxs (> fromIntegral idxLimit)) $ do + die "An offset exceeds the theoretical limit" + when (not $ and $ zipWith (<) idxs (tail idxs)) $ do + die "Offsets not strictly ascending" + let numOffsets = sum $ map (Bits.popCount . snd) bitmaps let nextOffset = \case [] -> Nothing (idx, bitmap) : k -> case popOffset bitmap of @@ -337,20 +343,36 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) offsets = unfoldr nextOffset bitmaps - -- get the txs - stmt_lookup_ebClosures <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (length offsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosures 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_lookup_ebClosures 2 ebHash - forM_ ([(3 :: DB.ParamIndex) ..] `zip` offsets) $ \(i, offset) -> do - withDie $ DB.bindInt64 stmt_lookup_ebClosures i (fromIntegral offset) - acc <- (\f -> foldM f [] offsets) $ \acc offset -> do - withDie (DB.stepNoCB stmt_lookup_ebClosures) >>= \case - DB.Done -> die $ "No rows starting at offset: " ++ show offset - DB.Row -> do - txOffset <- DB.columnInt64 stmt_lookup_ebClosures 0 - txCborBytes <- DB.columnBlob stmt_lookup_ebClosures 1 - when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset - pure (txCborBytes : acc) + -- get the txs, at most 'maxBatchSize' at a time + -- + -- TODO Better workaround for requests of many txs? + stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (maxBatchSize `min` numOffsets) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_lookup_ebClosuresMAIN 2 ebHash + withDieMsg $ DB.exec db (fromString "BEGIN") + acc <- (\f -> foldM f [] (batches offsets)) $ \acc batch -> do + stmt <- + if numOffsets <= maxBatchSize || length batch == maxBatchSize then pure stmt_lookup_ebClosuresMAIN else do + -- this can only be reached for the last batch + withDie $ DB.finalize stmt_lookup_ebClosuresMAIN + stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (numOffsets `mod` maxBatchSize) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_lookup_ebClosuresTIDY 2 ebHash + pure stmt_lookup_ebClosuresTIDY + forM_ ([(3 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do + withDie $ DB.bindInt64 stmt i (fromIntegral offset) + acc' <- (\f -> foldM f acc batch) $ \acc' offset -> do + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> die $ "No rows starting at offset: " ++ show offset + DB.Row -> do + -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? + txOffset <- DB.columnInt64 stmt 0 + txCborBytes <- DB.columnBlob stmt 1 + when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset + pure (txCborBytes : acc') + withDie $ DB.reset stmt + pure acc' + withDieMsg $ DB.exec db (fromString "COMMIT") -- combine the txs BS.putStr $ BS16.encode @@ -378,6 +400,16 @@ popOffset = \case in Just (zs, Bits.clearBit w (63 - zs)) +-- | Never request more than this many txs simultaneously +-- +-- TODO confirm this prevents the query string from exceeding its size limits, +-- even if the largest txOffsets are being requested. +maxBatchSize :: Int +maxBatchSize = 1024 + +batches :: [a] -> [[a]] +batches xs = if null xs then [] else take maxBatchSize xs : batches (drop maxBatchSize xs) + sql_lookup_ebClosures :: Int -> String sql_lookup_ebClosures n = "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ From cc1e3b6074acd286acad4acbe2e8679ba79d4638 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 10:51:21 -0700 Subject: [PATCH 014/119] leiosdemo202510: avoid reversing lists 2 --- ouroboros-consensus/app/leiosdemo202510.hs | 68 +++++++++++++++------- 1 file changed, 46 insertions(+), 22 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 3becf98d95..bdb290316a 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -306,12 +306,12 @@ msgLeiosBlockRequest db ebSlot ebHash = do txHash <- DB.columnBlob stmt_lookup_ebBodies 0 txSizeInBytes <- DB.columnInt64 stmt_lookup_ebBodies 1 loop $ pushX acc (txSizeInBytes, txHash) - y <- loop emptyX + acc <- loop emptyX -- combine the EB items BS.putStr $ BS16.encode $ serialize' - $ encodeEB fromIntegral id y + $ encodeEB fromIntegral id acc putStrLn "" -- | It's DESCending because the accumulator within the 'msgLeiosBlockRequest' @@ -331,31 +331,33 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do let maxEbByteSize = 12500000 :: Int minTxByteSize = 55 idxLimit = (maxEbByteSize `div` minTxByteSize) `div` 64 + when (any (== 0) $ map snd bitmaps) $ do + die "A bitmap is zero" when (flip any idxs (> fromIntegral idxLimit)) $ do - die "An offset exceeds the theoretical limit" + die $ "An offset exceeds the theoretical limit " <> show idxLimit when (not $ and $ zipWith (<) idxs (tail idxs)) $ do die "Offsets not strictly ascending" let numOffsets = sum $ map (Bits.popCount . snd) bitmaps - let nextOffset = \case + let nextOffsetDESC = \case [] -> Nothing - (idx, bitmap) : k -> case popOffset bitmap of - Nothing -> nextOffset k + (idx, bitmap) : k -> case (popRightmostOffset `asTypeOf` popLeftmostOffset) bitmap of + Nothing -> nextOffsetDESC k Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) - offsets = unfoldr nextOffset bitmaps + offsets = unfoldr nextOffsetDESC (reverse bitmaps) -- get the txs, at most 'maxBatchSize' at a time -- -- TODO Better workaround for requests of many txs? - stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (maxBatchSize `min` numOffsets) + stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (maxBatchSize `min` numOffsets) withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebSlot) withDie $ DB.bindBlob stmt_lookup_ebClosuresMAIN 2 ebHash withDieMsg $ DB.exec db (fromString "BEGIN") - acc <- (\f -> foldM f [] (batches offsets)) $ \acc batch -> do + acc <- (\f -> foldM f emptyX (batches offsets)) $ \acc batch -> do stmt <- if numOffsets <= maxBatchSize || length batch == maxBatchSize then pure stmt_lookup_ebClosuresMAIN else do -- this can only be reached for the last batch withDie $ DB.finalize stmt_lookup_ebClosuresMAIN - stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures (numOffsets `mod` maxBatchSize) + stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (numOffsets `mod` maxBatchSize) withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebSlot) withDie $ DB.bindBlob stmt_lookup_ebClosuresTIDY 2 ebHash pure stmt_lookup_ebClosuresTIDY @@ -369,7 +371,7 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do txOffset <- DB.columnInt64 stmt 0 txCborBytes <- DB.columnBlob stmt 1 when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset - pure (txCborBytes : acc') + pure $ pushX acc' txCborBytes withDie $ DB.reset stmt pure acc' withDieMsg $ DB.exec db (fromString "COMMIT") @@ -377,29 +379,49 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do BS.putStr $ BS16.encode $ serialize' - $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak (reverse acc) + $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak acc putStrLn "" {- | For example @ - print $ unfoldr popOffset 0 - print $ unfoldr popOffset 1 - print $ unfoldr popOffset (2^(34 :: Int)) - print $ unfoldr popOffset (2^(63 :: Int) + 2^(62 :: Int) + 8) + print $ unfoldr popLeftmostOffset 0 + print $ unfoldr popLeftmostOffset 1 + print $ unfoldr popLeftmostOffset (2^(34 :: Int)) + print $ unfoldr popLeftmostOffset (2^(63 :: Int) + 2^(62 :: Int) + 8) [] [63] [29] [0,1,60] @ -} -popOffset :: Word64 -> Maybe (Int, Word64) -{-# INLINE popOffset #-} -popOffset = \case +popLeftmostOffset :: Word64 -> Maybe (Int, Word64) +{-# INLINE popLeftmostOffset #-} +popLeftmostOffset = \case 0 -> Nothing w -> let zs = Bits.countLeadingZeros w in Just (zs, Bits.clearBit w (63 - zs)) +{- | For example +@ + print $ unfoldr popRightmostOffset 0 + print $ unfoldr popRightmostOffset 1 + print $ unfoldr popRightmostOffset (2^(34 :: Int)) + print $ unfoldr popRightmostOffset (2^(63 :: Int) + 2^(62 :: Int) + 8) + [] + [63] + [29] + [60,1,0] +@ +-} +popRightmostOffset :: Word64 -> Maybe (Int, Word64) +{-# INLINE popRightmostOffset #-} +popRightmostOffset = \case + 0 -> Nothing + w -> let zs = Bits.countTrailingZeros w + in + Just (63 - zs, Bits.clearBit w zs) + -- | Never request more than this many txs simultaneously -- -- TODO confirm this prevents the query string from exceeding its size limits, @@ -410,12 +432,14 @@ maxBatchSize = 1024 batches :: [a] -> [[a]] batches xs = if null xs then [] else take maxBatchSize xs : batches (drop maxBatchSize xs) -sql_lookup_ebClosures :: Int -> String -sql_lookup_ebClosures n = +-- | It's DESCending because the accumulator within the +-- 'msgLeiosBlockTxsRequest' logic naturally reverses it +sql_lookup_ebClosures_DESC :: Int -> String +sql_lookup_ebClosures_DESC n = "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ")\n\ - \ORDER BY ebClosures.txOffset\n\ + \ORDER BY ebClosures.txOffset DESC\n\ \" where hooks = intercalate ", " (replicate n "?") From ee4871bee2b371309b64d9074d6eee5e0b5aa409 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 13:09:42 -0700 Subject: [PATCH 015/119] leiosdemo202510: use map CBOR and handle MsgLeiosBlock --- ouroboros-consensus/app/leiosdemo202510.hs | 79 +++++++++++++++++++--- 1 file changed, 71 insertions(+), 8 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index bdb290316a..0b013bcbb7 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -10,7 +10,9 @@ module Main (main) where import Cardano.Binary (serialize') import qualified Cardano.Crypto.Hash as Hash +import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR +import qualified Codec.CBOR.Read as CBOR import Control.Monad (foldM, when) import qualified Data.Aeson as JSON import qualified Data.Bits as Bits @@ -54,6 +56,14 @@ main = getArgs >>= \case -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockRequest db ebSlot ebHash + ["MsgLeiosBlock", dbPath, ebPointStr, ebSlotStr, ebPath] + | ".db" `isSuffixOf` dbPath + , ".bin" `isSuffixOf` ebPath + , Just ebPoint <- readMaybe ebPointStr + , Just ebSlot <- readMaybe ebSlotStr + -> do + db <- withDieMsg $ DB.open (fromString dbPath) + msgLeiosBlock db ebPoint ebSlot ebPath "MsgLeiosBlockTxsRequest" : dbPath : ebSlotStr : ebHashStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath , Just ebSlot <- readMaybe ebSlotStr @@ -65,6 +75,7 @@ main = getArgs >>= \case _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ \ OR $0 MsgLeiosBlockRequest myDatabase.db ebSlot ebHash(hex)\n\ \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) ebSlot myEb.bin\n\ \" parseBitmaps :: [String] -> Maybe [(Word16, Word64)] @@ -260,19 +271,31 @@ withDieJust io = ----- -encodeEbItem :: (b -> Word16) -> (h -> ByteString) -> (b, h) -> CBOR.Encoding -encodeEbItem bytesToLen hashToBytes (txCborBytes, txHash) = - CBOR.encodeListLen 2 - <> CBOR.encodeBytes (hashToBytes txHash) +encodeEbPair :: (b -> Word16) -> (h -> ByteString) -> (b, h) -> CBOR.Encoding +encodeEbPair bytesToLen hashToBytes (txCborBytes, txHash) = + CBOR.encodeBytes (hashToBytes txHash) <> CBOR.encodeWord16 (bytesToLen txCborBytes) encodeEB :: Foldable f => (b -> Word16) -> (h -> ByteString) -> f (b, h) -> CBOR.Encoding -encodeEB bytesToLen hashToBytes ebItems = - CBOR.encodeListLenIndef +encodeEB bytesToLen hashToBytes ebPairs = + CBOR.encodeMapLenIndef <> foldr - (\x r -> encodeEbItem bytesToLen hashToBytes x <> r) + (\x r -> encodeEbPair bytesToLen hashToBytes x <> r) CBOR.encodeBreak - ebItems + ebPairs + +decodeEbPair :: CBOR.Decoder s (ByteString, Word16) +decodeEbPair = + (,) <$> CBOR.decodeBytes <*> CBOR.decodeWord16 + +_decodeEB :: CBOR.Decoder s (X (ByteString, Word16)) +_decodeEB = + CBOR.decodeMapLenIndef + *> CBOR.decodeSequenceLenIndef + pushX + emptyX + id + decodeEbPair ----- @@ -443,3 +466,43 @@ sql_lookup_ebClosures_DESC n = \" where hooks = intercalate ", " (replicate n "?") + +----- + +msgLeiosBlock :: DB.Database -> Int -> Word64 -> FilePath -> IO () +msgLeiosBlock db ebPoint ebSlot ebPath = do + ebBytes <- BS.readFile ebPath + let ebHash :: Hash.Hash HASH ByteString + ebHash = Hash.castHash $ Hash.hashWith id ebBytes + stmt_insert_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoints) + stmt_insert_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBodies) + withDieMsg $ DB.exec db (fromString "BEGIN") + -- INSERT INTO ebPoints + withDie $ DB.bindInt64 stmt_insert_ebPoints 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_insert_ebPoints 2 (Hash.hashToBytes ebHash) + withDie $ DB.bindInt64 stmt_insert_ebPoints 3 (fromIntegral ebPoint) + withDieDone $ DB.stepNoCB stmt_insert_ebPoints + withDie $ DB.reset stmt_insert_ebPoints + -- decode incrementally and simultaneously INSERT INTO ebBodies + let decodeBreakOrEbPair = do + stop <- CBOR.decodeBreakOr + if stop then pure Nothing else Just <$> decodeEbPair + let go1 txOffset bytes = do + (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrEbPair bytes + go2 txOffset bytes' next + go2 txOffset bytes = \case + Just (txHashBytes, txSizeInBytes) -> do + withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_insert_ebBodies 2 txOffset + withDie $ DB.bindBlob stmt_insert_ebBodies 3 txHashBytes + withDie $ DB.bindInt64 stmt_insert_ebBodies 4 (fromIntegral txSizeInBytes) + withDieDone $ DB.stepNoCB stmt_insert_ebBodies + withDie $ DB.reset stmt_insert_ebBodies + go1 (txOffset + 1) bytes + Nothing + | not (BSL.null bytes) -> die "Incomplete EB decode" + | otherwise -> pure () + (ebBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeMapLenIndef $ BSL.fromStrict ebBytes + go1 0 ebBytes2 + -- finalize the EB + withDieMsg $ DB.exec db (fromString "COMMIT") From 9ad22eae684ed177db9356c11a104abceea46b02 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 14 Oct 2025 13:37:59 -0700 Subject: [PATCH 016/119] leiosdemo202510: handle MsgLeiosBlockTxs --- ouroboros-consensus/app/leiosdemo202510.hs | 55 ++++++++++++++++++++-- 1 file changed, 52 insertions(+), 3 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 0b013bcbb7..6bd1cbbe09 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -72,10 +72,19 @@ main = getArgs >>= \case -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps + "MsgLeiosBlockTxs" : dbPath : ebPointStr : ebTxsPath : bitmapChunkStrs + | ".db" `isSuffixOf` dbPath + , ".bin" `isSuffixOf` ebTxsPath + , Just ebPoint <- readMaybe ebPointStr + , Just bitmaps <- parseBitmaps bitmapChunkStrs + -> do + db <- withDieMsg $ DB.open (fromString dbPath) + msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ \ OR $0 MsgLeiosBlockRequest myDatabase.db ebSlot ebHash(hex)\n\ - \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) ebSlot myEb.bin\n\ + \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlockTxs myDatabase.db ebPoint(int) myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ \" parseBitmaps :: [String] -> Maybe [(Word16, Word64)] @@ -363,7 +372,7 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do let numOffsets = sum $ map (Bits.popCount . snd) bitmaps let nextOffsetDESC = \case [] -> Nothing - (idx, bitmap) : k -> case (popRightmostOffset `asTypeOf` popLeftmostOffset) bitmap of + (idx, bitmap) : k -> case popRightmostOffset bitmap of Nothing -> nextOffsetDESC k Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) @@ -484,6 +493,7 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do withDieDone $ DB.stepNoCB stmt_insert_ebPoints withDie $ DB.reset stmt_insert_ebPoints -- decode incrementally and simultaneously INSERT INTO ebBodies + withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) let decodeBreakOrEbPair = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> decodeEbPair @@ -492,7 +502,6 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do go2 txOffset bytes' next go2 txOffset bytes = \case Just (txHashBytes, txSizeInBytes) -> do - withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) withDie $ DB.bindInt64 stmt_insert_ebBodies 2 txOffset withDie $ DB.bindBlob stmt_insert_ebBodies 3 txHashBytes withDie $ DB.bindInt64 stmt_insert_ebBodies 4 (fromIntegral txSizeInBytes) @@ -506,3 +515,43 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do go1 0 ebBytes2 -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") + +msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () +msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do + ebTxsBytes <- BSL.readFile ebTxsPath + stmt_insert_ebClosures <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosures) + withDie $ DB.bindInt64 stmt_insert_ebClosures 1 (fromIntegral ebPoint) + withDieMsg $ DB.exec db (fromString "BEGIN") + -- decode incrementally and simultaneously INSERT INTO ebClosures + -- + -- TODO also add to TxCache + let decodeBreakOrTx = do + stop <- CBOR.decodeBreakOr + if stop then pure Nothing else Just <$> CBOR.decodeBytes + let go1 offsets bytes = do + (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrTx bytes + go2 offsets bytes' next + go2 offsets bytes = \case + Just txBytes -> case offsets of + [] -> die "Too many txs" + txOffset:offsets' -> do + withDie $ DB.bindInt64 stmt_insert_ebClosures 2 $ fromIntegral txOffset + withDie $ DB.bindBlob stmt_insert_ebClosures 3 $ serialize' $ CBOR.encodeBytes txBytes + withDieDone $ DB.stepNoCB stmt_insert_ebClosures + withDie $ DB.reset stmt_insert_ebClosures + go1 offsets' bytes + Nothing + | not (BSL.null bytes) -> die "Incomplete EB txs decode" + | txOffset:_ <- offsets -> die $ "Too few EB txs; next is " <> show txOffset + | otherwise -> pure () + let nextOffset = \case + [] -> Nothing + (idx, bitmap) : k -> case popLeftmostOffset bitmap of + Nothing -> nextOffset k + Just (i, bitmap') -> + Just (64 * fromIntegral idx + i, (idx, bitmap') : k) + offsets = unfoldr nextOffset bitmaps + (ebTxsBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeListLenIndef ebTxsBytes + go1 offsets ebTxsBytes2 + -- finalize the EB + withDieMsg $ DB.exec db (fromString "COMMIT") From c4a938764d1d551a48088667d8082aed31e008b3 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 09:22:24 +0200 Subject: [PATCH 017/119] Implements immdb-node and Immutable DB NixOS systemd service --- nix/leios-mvd/genesis/genesis.byron.json | 4 +- nix/leios-mvd/immdb-node/config.json | 279 ++++++++++++++++++ .../immdb-node/immutable/00000.chunk | 0 .../immdb-node/immutable/00000.primary | Bin 0 -> 5 bytes .../immdb-node/immutable/00000.secondary | 0 nix/leios-mvd/immdb-node/os.nix | 7 + nix/leios-mvd/immdb-node/service.nix | 151 ++++++++++ nix/leios-mvd/leios-node/topology.json | 2 +- nix/leios-mvd/test.nix | 4 + 9 files changed, 444 insertions(+), 3 deletions(-) create mode 100644 nix/leios-mvd/immdb-node/config.json create mode 100644 nix/leios-mvd/immdb-node/immutable/00000.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00000.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00000.secondary create mode 100644 nix/leios-mvd/immdb-node/os.nix create mode 100644 nix/leios-mvd/immdb-node/service.nix diff --git a/nix/leios-mvd/genesis/genesis.byron.json b/nix/leios-mvd/genesis/genesis.byron.json index db3d32595d..e2bf95e287 100644 --- a/nix/leios-mvd/genesis/genesis.byron.json +++ b/nix/leios-mvd/genesis/genesis.byron.json @@ -37,6 +37,6 @@ , "txFeePolicy": { "summand": "0" , "multiplier": "439460" } , "unlockStakeEpoch": "184467" } -, "protocolConsts": { "k": 2160 , "protocolMagic": 42 } +, "protocolConsts": { "k": 3 , "protocolMagic": 42 } , "avvmDistr": {} -} \ No newline at end of file +} diff --git a/nix/leios-mvd/immdb-node/config.json b/nix/leios-mvd/immdb-node/config.json new file mode 100644 index 0000000000..3f923297e1 --- /dev/null +++ b/nix/leios-mvd/immdb-node/config.json @@ -0,0 +1,279 @@ +{ + "AlonzoGenesisFile": "genesis-alonzo.json", + "ByronGenesisFile": "genesis-byron.json", + "ConwayGenesisFile": "genesis-conway.json", + "ShelleyGenesisFile": "genesis-shelley.json", + "ChainSyncIdleTimeout": 0, + "EnableP2P": true, + "ExperimentalHardForksEnabled": true, + "ExperimentalProtocolsEnabled": true, + "LastKnownBlockVersion-Alt": 0, + "LastKnownBlockVersion-Major": 3, + "LastKnownBlockVersion-Minor": 0, + "PeerSharing": false, + "Protocol": "Cardano", + "RequiresNetworkMagic": "RequiresMagic", + "SnapshotInterval": 4230, + "SyncTargetNumberOfActivePeers": 15, + "SyncTargetNumberOfEstablishedPeers": 40, + "TargetNumberOfActivePeers": 15, + "TargetNumberOfEstablishedPeers": 40, + "TestAllegraHardForkAtEpoch": 0, + "TestAlonzoHardForkAtEpoch": 0, + "TestBabbageHardForkAtEpoch": 0, + "TestConwayHardForkAtEpoch": 0, + "TestMaryHardForkAtEpoch": 0, + "TestShelleyHardForkAtEpoch": 0, + "TraceOptionForwarder": { + "connQueueSize": 64, + "disconnQueueSize": 128, + "maxReconnectDelay": 30 + }, + "TraceOptionMetricsPrefix": "cardano.node.metrics.", + "TraceOptionNodeName": "immdb-node", + "TraceOptionPeerFrequency": 2000, + "TraceOptionResourceFrequency": 1000, + "TraceOptions": { + "": { + "backends": [ + "Stdout MachineFormat", + "EKGBackend", + "Forwarder" + ], + "detail": "DNormal", + "severity": "Notice" + }, + "BlockFetch.Client": { + "severity": "Debug" + }, + "BlockFetch.Client.CompletedBlockFetch": { + "maxFrequency": 2.0 + }, + "BlockFetch.Decision": { + "severity": "Notice" + }, + "BlockFetch.Remote": { + "severity": "Notice" + }, + "BlockFetch.Remote.Serialised": { + "severity": "Notice" + }, + "BlockFetch.Server": { + "severity": "Debug" + }, + "BlockchainTime": { + "severity": "Notice" + }, + "ChainDB": { + "severity": "Debug" + }, + "ChainDB.AddBlockEvent.AddBlockValidation": { + "severity": "Silence" + }, + "ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate": { + "maxFrequency": 2.0 + }, + "ChainDB.AddBlockEvent.AddedBlockToQueue": { + "maxFrequency": 2.0 + }, + "ChainDB.AddBlockEvent.AddedBlockToVolatileDB": { + "maxFrequency": 2.0 + }, + "ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB": { + "maxFrequency": 2.0 + }, + "ChainDB.LedgerEvent.Flavor.V1.OnDisk.BackingStoreEvent": { + "severity": "Silence" + }, + "ChainDB.LedgerEvent.Forker": { + "severity": "Silence" + }, + "ChainDB.ReplayBlock.LedgerReplay": { + "severity": "Notice" + }, + "ChainSync.Client": { + "severity": "Debug" + }, + "ChainSync.Local": { + "severity": "Notice" + }, + "ChainSync.Remote": { + "severity": "Notice" + }, + "ChainSync.Remote.Serialised": { + "severity": "Notice" + }, + "ChainSync.ServerBlock": { + "severity": "Notice" + }, + "ChainSync.ServerHeader": { + "severity": "Debug" + }, + "Consensus.GSM": { + "severity": "Info" + }, + "Forge.Loop": { + "severity": "Debug" + }, + "Forge.StateInfo": { + "severity": "Debug" + }, + "LedgerMetrics": { + "severity": "Info" + }, + "Mempool": { + "severity": "Debug" + }, + "Mempool.AttemptAdd": { + "severity": "Silence" + }, + "Mempool.LedgerFound": { + "severity": "Silence" + }, + "Mempool.LedgerNotFound": { + "severity": "Silence" + }, + "Mempool.SyncNotNeeded": { + "severity": "Silence" + }, + "Mempool.Synced": { + "severity": "Silence" + }, + "Net": { + "severity": "Notice" + }, + "Net.AcceptPolicy": { + "severity": "Debug" + }, + "Net.ConnectionManager.Local": { + "severity": "Debug" + }, + "Net.ConnectionManager.Remote": { + "severity": "Debug" + }, + "Net.ConnectionManager.Remote.ConnectionManagerCounters": { + "severity": "Silence" + }, + "Net.DNSResolver": { + "severity": "Notice" + }, + "Net.ErrorPolicy": { + "severity": "Info" + }, + "Net.ErrorPolicy.Local": { + "severity": "Debug" + }, + "Net.ErrorPolicy.Remote": { + "severity": "Debug" + }, + "Net.Handshake.Local": { + "severity": "Debug" + }, + "Net.Handshake.Remote": { + "severity": "Debug" + }, + "Net.InboundGovernor": { + "severity": "Warning" + }, + "Net.InboundGovernor.Local": { + "severity": "Debug" + }, + "Net.InboundGovernor.Remote": { + "severity": "Debug" + }, + "Net.InboundGovernor.Transition": { + "severity": "Debug" + }, + "Net.Mux.Local": { + "severity": "Notice" + }, + "Net.Mux.Remote": { + "severity": "Notice" + }, + "Net.PeerSelection": { + "severity": "Silence" + }, + "Net.PeerSelection.Actions": { + "severity": "Debug" + }, + "Net.PeerSelection.Counters": { + "detail": "DMinimal", + "severity": "Debug" + }, + "Net.PeerSelection.Initiator": { + "severity": "Notice" + }, + "Net.PeerSelection.Responder": { + "severity": "Notice" + }, + "Net.PeerSelection.Selection": { + "severity": "Debug" + }, + "Net.Peers.Ledger": { + "severity": "Debug" + }, + "Net.Peers.List": { + "severity": "Notice" + }, + "Net.Peers.LocalRoot": { + "severity": "Debug" + }, + "Net.Peers.PublicRoot": { + "severity": "Debug" + }, + "Net.Server.Local": { + "severity": "Debug" + }, + "Net.Server.Remote": { + "severity": "Debug" + }, + "Net.Subscription.DNS": { + "severity": "Debug" + }, + "Net.Subscription.IP": { + "severity": "Debug" + }, + "NodeState": { + "severity": "Notice" + }, + "Resources": { + "severity": "Debug" + }, + "Shutdown": { + "severity": "Notice" + }, + "Startup": { + "severity": "Notice" + }, + "Startup.DiffusionInit": { + "severity": "Debug" + }, + "StateQueryServer": { + "severity": "Notice" + }, + "TxSubmission.Local": { + "severity": "Notice" + }, + "TxSubmission.LocalServer": { + "severity": "Notice" + }, + "TxSubmission.MonitorClient": { + "severity": "Notice" + }, + "TxSubmission.Remote": { + "severity": "Notice" + }, + "TxSubmission.TxInbound": { + "severity": "Debug" + }, + "TxSubmission.TxOutbound": { + "severity": "Notice" + }, + "Version.NodeVersion": { + "severity": "Info" + } + }, + "TurnOnLogMetrics": true, + "TurnOnLogging": true, + "UseTraceDispatcher": true +} diff --git a/nix/leios-mvd/immdb-node/immutable/00000.chunk b/nix/leios-mvd/immdb-node/immutable/00000.chunk new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00000.primary b/nix/leios-mvd/immdb-node/immutable/00000.primary new file mode 100644 index 0000000000000000000000000000000000000000..51d72fb29fa4ae1f23b57813624cfc74777a7abe GIT binary patch literal 5 KcmZQ%00IC23IGBC literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00000.secondary b/nix/leios-mvd/immdb-node/immutable/00000.secondary new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/os.nix b/nix/leios-mvd/immdb-node/os.nix new file mode 100644 index 0000000000..633d638c57 --- /dev/null +++ b/nix/leios-mvd/immdb-node/os.nix @@ -0,0 +1,7 @@ +{immdb-server, ...}:{ + imports = [ + (import ./service.nix {inherit immdb-server;}) + ]; + + cardano.immdb-server.enable = true; +} diff --git a/nix/leios-mvd/immdb-node/service.nix b/nix/leios-mvd/immdb-node/service.nix new file mode 100644 index 0000000000..2b70a4e6d7 --- /dev/null +++ b/nix/leios-mvd/immdb-node/service.nix @@ -0,0 +1,151 @@ +{immdb-server, ...}: +{ + config, + lib, + pkgs, + ... +}: +let + cfg = config.cardano.immdb-server; +in +{ + + imports = [ + ]; + + options.cardano.immdb-server = { + enable = lib.mkEnableOption ''Run ourborous-consensus's immdb-server as a service''; + + db = lib.mkOption { + type = lib.types.path; + description = "Path to the ImmutableDB"; + default = ./immutable; + }; + + config = lib.mkOption { + type = lib.types.path; + description = "Path to config file, in the same format as for the node or db-analyser"; + default = ./config.json; + }; + + genesisAlonzo = lib.mkOption { + type = lib.types.path; + default = ../genesis/genesis.alonzo.json; + }; + + genesisConway = lib.mkOption { + type = lib.types.path; + default = ../genesis/genesis.conway.json; + }; + + genesisByron = lib.mkOption { + type = lib.types.path; + default = ../genesis/genesis.byron.json; + }; + + genesisShelley = lib.mkOption { + type = lib.types.path; + default = ../genesis/genesis.shelley.json; + }; + + port = lib.mkOption { + type = lib.types.port; + description = "Port to serve on"; + default = 3001; + }; + + user = lib.mkOption { + type = lib.types.str; + default = "immdb-server"; + description = ''User to run immdb-server service as.''; + }; + + group = lib.mkOption { + type = lib.types.str; + default = "immdb-server"; + description = ''Group to run immdb-server service as.''; + }; + + }; + + config = lib.mkIf cfg.enable { + users = { + users = { + ${cfg.user} = { + description = "User to run immdb-server service"; + inherit (cfg) group; + createHome = false; + isSystemUser = true; + }; + }; + + groups = { + ${cfg.group} = { + members = [ cfg.user ]; + }; + }; + }; + + networking.firewall.allowedTCPPorts = [ cfg.port ]; + + environment.etc = { + # "immdb-server/immutable/" = { + # user = cfg.user; + # group = cfg.group; + # mode = "0660"; + # source = cfg.db; + # }; + "immdb-server/config.json" = { + user = cfg.user; + group = cfg.group; + source = cfg.config; + }; + "immdb-server/genesis-alonzo.json" = { + user = cfg.user; + group = cfg.group; + source = cfg.genesisAlonzo; + }; + "immdb-server/genesis-conway.json" = { + user = cfg.user; + group = cfg.group; + source = cfg.genesisConway; + }; + "immdb-server/genesis-byron.json" = { + user = cfg.user; + group = cfg.group; + source = cfg.genesisByron; + }; + "immdb-server/genesis-shelley.json" = { + user = cfg.user; + group = cfg.group; + source = cfg.genesisShelley; + }; + + }; + + systemd.services.immdb-server = { + enable = true; + after = [ "network.target" ]; + wantedBy = [ "multi-user.target" ]; + serviceConfig = { + Restart = "on-failure"; + RemainAfterExit = true; + User = "immdb-server"; + Group = "immdb-server"; + ConfigurationDirectory = [ "immdb-server" ]; + StateDirectory = [ "immdb-server" ]; + }; + + path = [ immdb-server ]; + + script = '' + echo "Starting Immutable DB server with ${builtins.toJSON cfg}"; + mkdir $STATE_DIRECTORY/immutable; + cp -r ${cfg.db}/* $STATE_DIRECTORY/immutable; + immdb-server --db /var/lib/immdb-server/immutable --config /etc/immdb-server/config.json --port ${builtins.toString cfg.port}; + ''; + }; + + }; + +} diff --git a/nix/leios-mvd/leios-node/topology.json b/nix/leios-mvd/leios-node/topology.json index f478b45075..03857f79f9 100644 --- a/nix/leios-mvd/leios-node/topology.json +++ b/nix/leios-mvd/leios-node/topology.json @@ -5,7 +5,7 @@ "accessPoints": [ { "address": "immdb-node", - "port": 30001 + "port": 3001 } ], "advertise": false, diff --git a/nix/leios-mvd/test.nix b/nix/leios-mvd/test.nix index 221ced1845..45dadbd88c 100644 --- a/nix/leios-mvd/test.nix +++ b/nix/leios-mvd/test.nix @@ -3,12 +3,16 @@ name = "Leios MVD NixOS test"; nodes = { + immdb-node = import ./immdb-node/os.nix { + immdb-server = pkgs.hsPkgs.ouroboros-consensus-cardano.getComponent "exe:immdb-server"; + }; leios-node = import ./leios-node/os.nix {inherit inputs;}; }; testScript = '' start_all() + immdb_node.wait_for_unit("immdb-server.service") leios_node.wait_for_unit("cardano-node.service") ''; } From f78487be0a6663d412de1eb76e093e8b766113fe Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 11:31:58 +0200 Subject: [PATCH 018/119] Add `--address` flag to `immdb-server` executable --- .../app/immdb-server.hs | 40 +++++++++++++------ 1 file changed, 27 insertions(+), 13 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index 5e118362ef..9fc036ba17 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -7,27 +7,35 @@ import Cardano.Crypto.Init (cryptoInit) import qualified Cardano.Tools.DBAnalyser.Block.Cardano as Cardano import Cardano.Tools.DBAnalyser.HasAnalysis (mkProtocolInfo) import qualified Cardano.Tools.ImmDBServer.Diffusion as ImmDBServer -import Data.Void +import Data.Void (absurd) import Main.Utf8 (withStdTerminalHandles) +import Network.Socket (AddrInfo (addrFlags, addrSocketType)) import qualified Network.Socket as Socket -import Options.Applicative +import Options.Applicative (ParserInfo, execParser, fullDesc, help, + helper, info, long, metavar, progDesc, showDefault, + strOption, value) import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) main :: IO () main = withStdTerminalHandles $ do cryptoInit - Opts {immDBDir, port, configFile} <- execParser optsParser - let sockAddr = Socket.SockAddrInet port hostAddr - where - -- could also be passed in - hostAddr = Socket.tupleToHostAddress (127, 0, 0, 1) - args = Cardano.CardanoBlockArgs configFile Nothing + Opts {immDBDir, port, address, configFile} <- execParser optsParser + + let hints = Socket.defaultHints { addrFlags = [Socket.AI_NUMERICHOST], addrSocketType = Socket.Stream} + addrInfo <- do + addrInfos <- Socket.getAddrInfo (Just hints) (Just address) (Just port) + case addrInfos of + [] -> error "Invalid address or port" + addrInfo:_ -> return addrInfo + + let args = Cardano.CardanoBlockArgs configFile Nothing ProtocolInfo{pInfoConfig} <- mkProtocolInfo args - absurd <$> ImmDBServer.run immDBDir sockAddr pInfoConfig + absurd <$> ImmDBServer.run immDBDir (Socket.addrAddress addrInfo) pInfoConfig data Opts = Opts { immDBDir :: FilePath - , port :: Socket.PortNumber + , port :: String + , address :: String , configFile :: FilePath } @@ -43,10 +51,16 @@ optsParser = , help "Path to the ImmutableDB" , metavar "PATH" ] - port <- option auto $ mconcat + port <- strOption $ mconcat [ long "port" , help "Port to serve on" - , value 3001 + , value "3001" + , showDefault + ] + address <- strOption $ mconcat + [ long "address" + , help "Address to serve on" + , value "127.0.0.1" , showDefault ] configFile <- strOption $ mconcat @@ -54,4 +68,4 @@ optsParser = , help "Path to config file, in the same format as for the node or db-analyser" , metavar "PATH" ] - pure Opts {immDBDir, port, configFile} + pure Opts {immDBDir, port, address, configFile} From 62db8e4fbd8effa0bfffb183d8ff0015f05333b9 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 11:33:57 +0200 Subject: [PATCH 019/119] Add `address` options to `immdb-server` NixOS service --- nix/leios-mvd/immdb-node/service.nix | 33 ++++++++++++++++------------ 1 file changed, 19 insertions(+), 14 deletions(-) diff --git a/nix/leios-mvd/immdb-node/service.nix b/nix/leios-mvd/immdb-node/service.nix index 2b70a4e6d7..27d80f1ce0 100644 --- a/nix/leios-mvd/immdb-node/service.nix +++ b/nix/leios-mvd/immdb-node/service.nix @@ -1,9 +1,8 @@ -{immdb-server, ...}: -{ - config, - lib, - pkgs, - ... +{ immdb-server, ... }: +{ config +, lib +, pkgs +, ... }: let cfg = config.cardano.immdb-server; @@ -48,6 +47,12 @@ in default = ../genesis/genesis.shelley.json; }; + address = lib.mkOption { + type = lib.types.str; + description = "Address to serve on"; + default = "0.0.0.0"; + }; + port = lib.mkOption { type = lib.types.port; description = "Port to serve on"; @@ -89,12 +94,6 @@ in networking.firewall.allowedTCPPorts = [ cfg.port ]; environment.etc = { - # "immdb-server/immutable/" = { - # user = cfg.user; - # group = cfg.group; - # mode = "0660"; - # source = cfg.db; - # }; "immdb-server/config.json" = { user = cfg.user; group = cfg.group; @@ -140,10 +139,16 @@ in script = '' echo "Starting Immutable DB server with ${builtins.toJSON cfg}"; + mkdir $STATE_DIRECTORY/immutable; cp -r ${cfg.db}/* $STATE_DIRECTORY/immutable; - immdb-server --db /var/lib/immdb-server/immutable --config /etc/immdb-server/config.json --port ${builtins.toString cfg.port}; - ''; + + immdb-server \ + --db $STATE_DIRECTORY/immutable \ + --config $CONFIGURATION_DIRECTORY/config.json \ + --address ${cfg.address} \ + --port ${builtins.toString cfg.port}; + ''; }; }; From 5b454c2620331ba67ad45eaaabb525c9eadfa774 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 11:34:44 +0200 Subject: [PATCH 020/119] DNS tweaks to Leios MVD and formatting --- flake.nix | 2 +- nix/leios-mvd/immdb-node/os.nix | 4 ++-- nix/leios-mvd/leios-node/os.nix | 2 +- nix/leios-mvd/leios-node/topology.json | 2 +- nix/leios-mvd/test.nix | 22 +++++++++++++++++----- 5 files changed, 22 insertions(+), 10 deletions(-) diff --git a/flake.nix b/flake.nix index e2157af61a..79ba2958b9 100644 --- a/flake.nix +++ b/flake.nix @@ -89,7 +89,7 @@ legacyPackages = pkgs; packages = hydraJobs.native.haskell96.exesNoAsserts.ouroboros-consensus-cardano // { - leios-mvd-test = pkgs.testers.nixosTest (import ./nix/leios-mvd/test.nix {inherit inputs pkgs;}); + leios-mvd-test = pkgs.testers.nixosTest (import ./nix/leios-mvd/test.nix { inherit inputs pkgs; }); }; } ); diff --git a/nix/leios-mvd/immdb-node/os.nix b/nix/leios-mvd/immdb-node/os.nix index 633d638c57..8b225d23fa 100644 --- a/nix/leios-mvd/immdb-node/os.nix +++ b/nix/leios-mvd/immdb-node/os.nix @@ -1,6 +1,6 @@ -{immdb-server, ...}:{ +{ immdb-server, ... }: { imports = [ - (import ./service.nix {inherit immdb-server;}) + (import ./service.nix { inherit immdb-server; }) ]; cardano.immdb-server.enable = true; diff --git a/nix/leios-mvd/leios-node/os.nix b/nix/leios-mvd/leios-node/os.nix index f5e9786500..c71b57c8a5 100644 --- a/nix/leios-mvd/leios-node/os.nix +++ b/nix/leios-mvd/leios-node/os.nix @@ -1,4 +1,4 @@ -{inputs, ...}:{ +{ inputs, ... }: { imports = [ inputs.cardano-nix.nixosModules.default ]; diff --git a/nix/leios-mvd/leios-node/topology.json b/nix/leios-mvd/leios-node/topology.json index 03857f79f9..ddd7b0e98c 100644 --- a/nix/leios-mvd/leios-node/topology.json +++ b/nix/leios-mvd/leios-node/topology.json @@ -4,7 +4,7 @@ { "accessPoints": [ { - "address": "immdb-node", + "address": "immdb-node.local", "port": 3001 } ], diff --git a/nix/leios-mvd/test.nix b/nix/leios-mvd/test.nix index 45dadbd88c..31af30ed9c 100644 --- a/nix/leios-mvd/test.nix +++ b/nix/leios-mvd/test.nix @@ -1,12 +1,24 @@ -{inputs, pkgs, ...}: +{ inputs, pkgs, ... }: { name = "Leios MVD NixOS test"; nodes = { - immdb-node = import ./immdb-node/os.nix { - immdb-server = pkgs.hsPkgs.ouroboros-consensus-cardano.getComponent "exe:immdb-server"; + immdb-node = { + imports = [ + (import ./immdb-node/os.nix { + immdb-server = pkgs.hsPkgs.ouroboros-consensus-cardano.getComponent "exe:immdb-server"; + }) + ]; + networking.domain = "local"; + }; + leios-node = { + imports = [ + (import ./leios-node/os.nix { inherit inputs; }) + ]; + networking.domain = "local"; + environment.systemPackages = [ pkgs.dnsutils ]; + services.resolved.enable = true; }; - leios-node = import ./leios-node/os.nix {inherit inputs;}; }; testScript = '' @@ -14,5 +26,5 @@ immdb_node.wait_for_unit("immdb-server.service") leios_node.wait_for_unit("cardano-node.service") - ''; + ''; } From 7c25e7f1d6c7baae1cedf8ef0d44a4aaba794c47 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 13:45:36 +0200 Subject: [PATCH 021/119] Add immutable db fixture (50 blocks) --- nix/leios-mvd/immdb-node/immutable/00000.chunk | Bin 0 -> 1026 bytes nix/leios-mvd/immdb-node/immutable/00000.primary | Bin 5 -> 129 bytes .../immdb-node/immutable/00000.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00001.chunk | Bin 0 -> 3420 bytes nix/leios-mvd/immdb-node/immutable/00001.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00001.secondary | Bin 0 -> 224 bytes nix/leios-mvd/immdb-node/immutable/00002.chunk | Bin 0 -> 1710 bytes nix/leios-mvd/immdb-node/immutable/00002.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00002.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00003.chunk | Bin 0 -> 2565 bytes nix/leios-mvd/immdb-node/immutable/00003.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00003.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00004.chunk | Bin 0 -> 855 bytes nix/leios-mvd/immdb-node/immutable/00004.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00004.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00005.chunk | Bin 0 -> 1710 bytes nix/leios-mvd/immdb-node/immutable/00005.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00005.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00006.chunk | Bin 0 -> 2565 bytes nix/leios-mvd/immdb-node/immutable/00006.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00006.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00007.chunk | Bin 0 -> 855 bytes nix/leios-mvd/immdb-node/immutable/00007.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00007.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00008.chunk | Bin 0 -> 855 bytes nix/leios-mvd/immdb-node/immutable/00008.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00008.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00009.chunk | Bin 0 -> 856 bytes nix/leios-mvd/immdb-node/immutable/00009.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00009.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00010.chunk | Bin 0 -> 1712 bytes nix/leios-mvd/immdb-node/immutable/00010.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00010.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00011.chunk | Bin 0 -> 2568 bytes nix/leios-mvd/immdb-node/immutable/00011.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00011.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00012.chunk | Bin 0 -> 1714 bytes nix/leios-mvd/immdb-node/immutable/00012.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00012.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00013.chunk | Bin 0 -> 1714 bytes nix/leios-mvd/immdb-node/immutable/00013.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00013.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00014.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00014.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00014.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00015.chunk | 0 nix/leios-mvd/immdb-node/immutable/00015.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00015.secondary | 0 nix/leios-mvd/immdb-node/immutable/00016.chunk | Bin 0 -> 1714 bytes nix/leios-mvd/immdb-node/immutable/00016.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00016.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00017.chunk | 0 nix/leios-mvd/immdb-node/immutable/00017.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00017.secondary | 0 nix/leios-mvd/immdb-node/immutable/00018.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00018.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00018.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00019.chunk | Bin 0 -> 2571 bytes nix/leios-mvd/immdb-node/immutable/00019.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00019.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00020.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00020.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00020.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00021.chunk | 0 nix/leios-mvd/immdb-node/immutable/00021.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00021.secondary | 0 nix/leios-mvd/immdb-node/immutable/00022.chunk | 0 nix/leios-mvd/immdb-node/immutable/00022.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00022.secondary | 0 nix/leios-mvd/immdb-node/immutable/00023.chunk | Bin 0 -> 1714 bytes nix/leios-mvd/immdb-node/immutable/00023.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00023.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00024.chunk | Bin 0 -> 2571 bytes nix/leios-mvd/immdb-node/immutable/00024.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00024.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00025.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00025.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00025.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00026.chunk | Bin 0 -> 2571 bytes nix/leios-mvd/immdb-node/immutable/00026.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00026.secondary | Bin 0 -> 168 bytes nix/leios-mvd/immdb-node/immutable/00027.chunk | Bin 0 -> 1714 bytes nix/leios-mvd/immdb-node/immutable/00027.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00027.secondary | Bin 0 -> 112 bytes nix/leios-mvd/immdb-node/immutable/00028.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00028.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00028.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00029.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00029.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00029.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00030.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00030.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00030.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00031.chunk | 0 nix/leios-mvd/immdb-node/immutable/00031.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00031.secondary | 0 nix/leios-mvd/immdb-node/immutable/00032.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00032.primary | Bin 0 -> 129 bytes .../immdb-node/immutable/00032.secondary | Bin 0 -> 56 bytes nix/leios-mvd/immdb-node/immutable/00033.chunk | Bin 0 -> 857 bytes nix/leios-mvd/immdb-node/immutable/00033.primary | Bin 0 -> 29 bytes .../immdb-node/immutable/00033.secondary | Bin 0 -> 56 bytes 102 files changed, 0 insertions(+), 0 deletions(-) create mode 100644 nix/leios-mvd/immdb-node/immutable/00001.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00001.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00001.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00002.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00002.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00002.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00003.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00003.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00003.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00004.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00004.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00004.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00005.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00005.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00005.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00006.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00006.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00006.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00007.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00007.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00007.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00008.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00008.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00008.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00009.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00009.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00009.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00010.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00010.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00010.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00011.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00011.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00011.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00012.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00012.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00012.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00013.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00013.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00013.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00014.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00014.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00014.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00015.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00015.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00015.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00016.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00016.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00016.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00017.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00017.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00017.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00018.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00018.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00018.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00019.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00019.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00019.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00020.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00020.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00020.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00021.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00021.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00021.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00022.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00022.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00022.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00023.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00023.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00023.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00024.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00024.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00024.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00025.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00025.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00025.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00026.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00026.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00026.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00027.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00027.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00027.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00028.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00028.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00028.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00029.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00029.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00029.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00030.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00030.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00030.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00031.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00031.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00031.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00032.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00032.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00032.secondary create mode 100644 nix/leios-mvd/immdb-node/immutable/00033.chunk create mode 100644 nix/leios-mvd/immdb-node/immutable/00033.primary create mode 100644 nix/leios-mvd/immdb-node/immutable/00033.secondary diff --git a/nix/leios-mvd/immdb-node/immutable/00000.chunk b/nix/leios-mvd/immdb-node/immutable/00000.chunk index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..0b766c8ee437e06d830b651fa7773de5dde67c54 100644 GIT binary patch literal 1026 zcmV+d1pWJh2Ze%)00Q<{AZrs&bL|Y$PiV-X?FjuO-QT>bHbrBvG=QZi_epguxmX~r z8<&tu(VcLEq8IWwUWpNj{sl%snH2}39@Zw^$$7e53M+Dc z{-ME2jE>!yg{(mFtR_7!LYP)X^|-}8wQPKw$i#wY|5?O3cUh@Y+umoYpwC!PeJZ`+ zHATOJ;;?~ibu{{jG1&_T4U5#}+F%5w@Wv~ikweyO@S-1UrgQm46MWCc*i@3k;`ODj#(+4+7ksM)RKl;hOAeU z&#=Rb1D4Y)gjgWleK#24dEE3VCA07VSS!)hwUGWuD7*Eya#)4k3uhJp09Zf}*I}VM zRtW};jfE{t_&wyq(gJefBTwpd#Aa8<3R$ok*8Y#VErT;SH54Q8%bGS8HiHwB5`VTn zTyH9|qrVG+3IkaIzySA>U>jwIr}Gy5)NA}$Dp~0=4eNL-U(COgkGQuTIM^Q?f2|x4 zGwQs+Qq}@)(8{?56hcET=!Jm+sjdi-3~7sIYqC!zU?WOae6|+eyhqxKpz&B9u3orS z2SP>(e*^Ts(Ug2<(TAL^-ZDCF9kk<98!z)5_w&JwM2%6@Tn;aF+wN%Wqp-FVkTV-Y ztmQUVrct(kz64GQRn59_Wcexv*^4$n3{nEDLcj2TwD!!*`-H&Lh-sX@B9r`-VK1O$ ziR!A8a}YhBq*?xbFzIr5b)2MX>Ecy$a0u{|9zUF4x)@h>ou$&0sLe)I_tZJypmbDjY1c04KD-5I#i=}{1wmXjBs zJ`bM99^6J(XK45y5y$@B?{(fLRXa8UPPMKm!^84?;kJp#a$d0)c{9AP$V) zPa2?pz9TuZ^?AW?JiJ8@+S=jgn> wSk5L8UetWzNkFcixb3=!>23Kd#-2--z)87^oLe>K&C)UPHlV&v^D+pafK-a}N&o-= literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00000.primary b/nix/leios-mvd/immdb-node/immutable/00000.primary index 51d72fb29fa4ae1f23b57813624cfc74777a7abe..9dffe10d00c85c8d44e3c0d8e1dba5b0573c54c7 100644 GIT binary patch literal 129 PcmZQ%zyuaRA-Z7zQSk;M literal 5 KcmZQ%00IC23IGBC diff --git a/nix/leios-mvd/immdb-node/immutable/00000.secondary b/nix/leios-mvd/immdb-node/immutable/00000.secondary index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..b6572daf2674029b3cc6d8ac3a96dca6e72315a2 100644 GIT binary patch literal 56 zcmZQzfC6S_eNOq5a=*#9HY%=qwO?V`HbDgsHU5p;^=|qLyw*3Ctz?Ye;{F1vnh5}y C0}nL- literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00001.chunk b/nix/leios-mvd/immdb-node/immutable/00001.chunk new file mode 100644 index 0000000000000000000000000000000000000000..d38df30fe536989d65e21a51ad66e17ef3a75514 GIT binary patch literal 3420 zcmeIz`8U*y0swIP7GY$_IwUdC2!kSokZYM?%zP~k5(ZharjR{T_910t$xR(^Jd!)Us2GxcTIo%(-dRAGSbv$E&4kd#p-WrWO%3B8{%CYrmc0EJR z2h5xAY3ZS^w1?Sc6Uvvp#cRG>iNb!0?fm?ZV33IHvp)$799_XJ7gUf>rKpJNm(Ho7 zi;?69?^(<_t-BlV+}eY(4L?@X<+fxh)oWgRP_s>?9>lbKi+9g{FHJa1cY@{J!v7!< z{Q0ir7TO$#DJ}Zl4a_d|Se&u;_vKh4Na$ocGzw#ao)`6|zv?!$-s!tUugedp$OdyV zhNO>;*G!?AU*O#{lI1hnyT-274_^bosY|gEQ|gmT^-RGkKCLJc zkw@>#q*b>^avO+Ua%kz*cu!Raz37kvLJ2zf=P;}UX~~a{pRT7ZBKe*@AqeGa^X7C& zj2U9waJv%x9mnIVffKUm>U9|mf4(bu(@kO%%~2|#U5(yaa5=DV(*6{ZxA4+v_T5M5 z-T4d2A+$`^^Tq2T4471*&_O`0?AJ0A3@ns5?pq6c_uO?OxS>EKA|fv$>JL^-!m0q| zordW`h$4O@i%b*eJM=B^kbCxfTO|*{IVcTk*4)h3l0TiC*j{7=22|&WtF_z&GpzRg7_e zbf;dxZN`f(Yh|skkK5OK9qwPPD&LcPZ5rnwY8-4UJnf!iaGyU3ZzJw{3HR*e9`9ZD z+Nwf%Yo`iXGj{-CGQo3jp40EbUI@+cV{ahnOM!Y$m>9er{mRJX$mKj5Ha_QrBJ-Q1{F*CFFmD}3g-)DB^>d>^ zd~LIfIl}6FDIJLnA^UIoecIJGerI=l4t{dc?q{6>n-B;DqU^?80L|TdJKu&+Mu|Z*9~Qcg?z$3?KLoW%blDR^c9t5({bk zMOJlSCitiov2fwC^Ms=6<}(=*JZ(c+bz}vM*YY4GNH4;b2ARSLg0oBe{(VKu#5^sM zQfJ2AV(?d|)*0jV^I|u~Ja)aC$Cir`Uhh7`Z=n_^&-scjZ&KjKC9E}t6X~-Y6O>V; zv)$CP+@+#Jg)Onhktdc8G)xvXnX^o3VE?i{HdLwVf~&vC2M(tO=@XZ)1^fHJR9=>p zA>cb1Uk+{$Q>sE8xQH|C)V8o`2%Fb0hB&FR@Xi|m2O_d1z(w34JG|PNZnbUs6$Z}5 znnPDjO1LXDm6oZXJk+!#+tLB68Np94UciP9OlEAw-r=0<-emQb)}Qk{y6hr!0BEs! z6F(#MHZ#fNMyv3jfmWCP%ZgbT4nWRSNbSzFc;BjIGa6p0?Oc~Y2us?c(`9CJWsJA` zcVGQQTbXiWYa4w9kFS&n<5Mpl%*CR4>KdR!QnZVA6Q|3CsVhbQlKh>~$!_zHF;N@TXX^LM#c^ec zR$@Qw(D(lLx-w$g-pHOA|yKUv% zk(Hg<+I`PBpRN=cg99mA)-X_carZWI9zPSZx;nLX&=K!CC==VKXxp!s#Ox@w6C1nQ zzLxul%dOSauY~oVt^Ouku?TAd5NtQ7+Sw(D@KfTZo{;Pz<=ovQx)-bp+BhT&lyr|UeyftgvMOlGA1&gyZWNA1RZ0kV! z*pz2;#+?<~oSa%V`LkS-lepTSBkC1>Z*%oGY3;fp)oQ44J`$?W6hd>cg7oc5IT_9D o_@Xji_}ZSmyz+1O57=*yyVrB=dgRQ5Gu=M#*5P;dgX*&e0CDU~c>n+a literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00002.chunk b/nix/leios-mvd/immdb-node/immutable/00002.chunk new file mode 100644 index 0000000000000000000000000000000000000000..c621457caaa9e95daa2ef9e0a3eb2c6c25585d73 GIT binary patch literal 1710 zcmV;f22uHf2Ze%)1sF|OAOk_@d0!LOyuA${><_>{w_e_i*4J5?!I?($yDSewPFNt2 z$5e2ymorMX!;}z|#f4E;DbiS4e12+Jq!|o`(Ba=$AbvMjQhtCE_I4T^cfq<-#FVKm z2oy5^ktNm&-l%kuoQG%~)fi{_uLZGsc=sdY4b)@otim0-F z2(Ys(t#GYZW@|L2;f^Fgiy#0`=*JRRi3OcbSWrMM)g}az)JvW0(T)|pGb^@$(9keF zL+t@tAuGMK$JMoA<+k=(qahovp-K6eQ7O9v>mV!ogP6(V<|-(*t8ONp$T;5I)W)NvASqWJ7Vv>^n>-jVayFbShG(*KtA6j1A@q}0)-HBWGetQGN zTV5n4*oC!T8bWvaKSI@sXgEL#Z?km5003A(&M2OW*+?gERJIXHkpJbRj84MYRD9kg zRMiYt5)i}W>7E!j)R4!G0D1ba)o;Z&^5zF%ofeicTVkXAV*7juf(ip!0l=+6j)f{I z#9X@kzVzgg=X8I07|BLgPxt~H@_hgN%Kji7+K4WwplCCWOOR%)w5-LE?&{yq`!fm@ z&+b`*ngQ?us%{_CIGXU01&K^ZbYWM|xXr5XgH%MeL1ELZYrk3~{lX%qfS6Dpm>(hd z%*&S#DuE5#%Zud?!@&OqxGlN7(_p!zVW&d(XOUZT4dm|=(zSw?X*;*>m2Wlo#P1aB zUMzY9Fa)aIqMEaHmlplPQ0Oi?W8N(^^qC~8HIni&G}`VKi9Bkmj3VhZFxLWolNIFa z`g7E!?3?k><{4Dhxy4sdfU(r{Z%#R7JFxL7yLtcC^vMy$G8o>x*xgrZX zMR#*=FEgj9txz@hmCpNY*~GGZUkaPz2h78L;UETW{{V&|t$xW}SO`#oz;tCDUz~ok zW9?J+QqV6JpI%NX?@Fl*usbm9%o3nf;U5O;`vpytazcm`S?yTgmGy;j3FXc71#Tik z`W9N+3Q zN@uE{qP32YxIf!#EeU#6@U?n3SRiW?PIK)H(obl}pzR3#B;DV=Oc$m$q9rIO^Ug7Ho! z+I7TsKADpOA4TN3xhLUazj^yU3w!vm-_skYbRk;kFHY+I3V&wu9r4j#hRn#BL%=Lp zP|8`JXe4hk%!NR=j0&2UZjY-xwnAjmr-RtL%}Bxf z)#J{C#U_)Gt?8C23j88C(axDe#WRa&`9xL600dYdDOVj9@PTlfJV<32U3m4r3Wxx!bKxq4IKUo+~>xK(e*^Ts(Ug2<(TAL^-ZDCF9kk<98!z)5_w&JwM2%6@Tn;aF+wN%Wqp-FV zkTV-YtmQUVrct(kz64GQRn59_Wcexv*^4$n3{nEDLcj2TwD!!*`-H&Lh-sX@B9r`- zVK1O$iR!A8a}YhBq*?xbFzIr5b)2MX>Ecy$a0u{|9zUF4x)@h>ou$&0sLe)I_tZJ< zx1n^foE8ZId6eAUwBS|)qKRphk13VK%iKk{*-?myPypmbDjY1c04KD-5I#i=}{1w zmXjBsJ`bM99^6J(XK45y5y$@B?{(fLRi_@% literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00002.primary b/nix/leios-mvd/immdb-node/immutable/00002.primary new file mode 100644 index 0000000000000000000000000000000000000000..3dd3ca8e9b5b3dd35643e53efe95f7149607cf74 GIT binary patch literal 129 UcmZQ%pf0cg8VAD#KsG@P0CB1X3IG5A literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00002.secondary b/nix/leios-mvd/immdb-node/immutable/00002.secondary new file mode 100644 index 0000000000000000000000000000000000000000..06acc09aca52acc77982bfaac9eaaa75dd828d19 GIT binary patch literal 112 zcmZQzfC6UbfRhY&R~V|eU8&i(xlQK&D`T(pRr42Z?VGT}{&u!5XI1EjtyShw)xHp# xIh+Bguh_f4XWQI&!OJSO=cjF7XrE{udX9H<$;J=z+cP=TV=Wjw4Wgj>0ssQ_Bd`Df literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00003.chunk b/nix/leios-mvd/immdb-node/immutable/00003.chunk new file mode 100644 index 0000000000000000000000000000000000000000..2016ff4c7f44d4eb523fa069139d7c3a276665ad GIT binary patch literal 2565 zcmeIx`8U*y0s!zawo$rSYRpAu62gQj28|_6SrTO#Ghe$QvXeC$OqQ;(9LjF&WV=LU z7%E{jbwfyn%-G$83L_xT?_v4RP)NrEtE06{DKZe1CHEcR$E zy+qWp893G)@{|K_^@5yr)COHc*#QV2@f*P_!oxQ`-;}IC4&+#q&ucXe-5NB=kI!yj z3q3~%5cN_y>83-4fpKLL>)K8fQOY5|(dBtX^2ec1e*+elUDYUR3(_Fk3d)5WxjE?iSgd!v=cOFwy#NI#>|_`a?K za&z>8=I9&efq8fRTyQnv^mg(1b^Bsm6r8k7_$15+Ae0EFpq%@GR9zEyn2X@Or5%kU z9haEm8drL6!tI{X zCYI{pg#=Pl6I9H8=*{&EgM+5e-24{8@F2WCV%sSB=`fA15~r?>K5>TgE?*O>87H10 z7DLl_2vB}n-gz|k2(K;As|K;$*X$ju@wqKC8>On8r>YkUGm8*CgSTw%)~T)1{keAy z8QN-1AmiylUmxB=^lNt5`4=5VS9S2S6*XnEN4=6ge41{`yPPq_lW0)(bK~)(k~Ki) ziBlV15Njk9!^?d+lu7a!`mLazeF5Wt>e;Ndl-h>$_C{CA)l|z7hhNk}zkK&xE^nlr zNLQD-Qa7)Oue7AayyUwfWYgb%=hlw0z*w@Tfv^?04%^9zdA8Npw-^8FL!wu~OWBP5 zOrl!JEy}mrj9?MH;tJctDAZ!m-Oz#x@5LFL;6Ml`L*`O}b32R>R`_^0v%25NW_#q~ zN^5CIV*yl%Cn9r#^=t~yTSoE9N>j?}eK%p)HfEWaXb~|t_Ch!YvP)iB>sv~YnbMkE zY6FL>2Xy0VsmHJblh*y-X+2_s@X@7e*83*r%Hw^881AHVa1rQxn6Ab7p z?BA^*Fkb+{>5i{9PjL;~ytp9gNr@Px;>_=pTAc&U&pB6X=ec+Sh;$|{upvj?l-83e zlG&SJiB}p1>`2kxK*g`Z4+f_v0YtPG!77?8wiPBR9p2S$&B&}#ft-9I=D)s}@4a^2 z$nhVo!ei!2zq~@GVRrHZ%j->(sd4AX%&=C%d zrgFzuw&dGJv2ouI44+kwDsneR{{1F3cGGhGO+bfKJgamx?{^aynSzu9-hZzZi(nOiJ^X^o^aQ$Z2C4Icw~wbmB|T?(Pu=j~m~4_x<1kbkyn$~JR=odV*0 zrf!>-);RRkSy{}6zzyt)O(v*p_(E)x0T-5dP$3|WGIneBT~Y)X4Q`%XE&9>=1VP>Qa1ZHnw78ub|*m2q-zX*YP} z@iMhUw-)s_YiBWhkk~zAvWAp)obdkP-#M{dY2o+c5A-eE;^f&tsbww$ZBoPktb(06 z2Vpb5Si0FyEh}Dpynk*}x_vy`%6W*8-n$ zHT9~RdJFV+*1(?c7^8{ge1tk9*w+&^jS%qr33_n4KKiXA0I|6LD#ZPib3t^o+luv; z)u0-**y)Dys%edIqYi4hPpkwt4HsD2<2TO;!X}E_t^ku+n+bP>=KHz){<2r*eGV}0 z5_^EIfIsyQODs2s#xh<-Z-iQ3{8uX>SO9>aKd2EhKFMkLC6vK7&(L8XK0rfj$00>jYxf3aOPrE5C!a-sNpGv2K~R)f4|jVorLYd literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00003.primary b/nix/leios-mvd/immdb-node/immutable/00003.primary new file mode 100644 index 0000000000000000000000000000000000000000..31a0a654e4a674c6c40149fd621592fa6e55c858 GIT binary patch literal 129 YcmZQ%zz-~d(xl=7pdJ`r0c7LF0BYe15&!@I literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00003.secondary b/nix/leios-mvd/immdb-node/immutable/00003.secondary new file mode 100644 index 0000000000000000000000000000000000000000..b7e6e3e3c1aa2383f6b059ea5bf80c76b335535f GIT binary patch literal 168 zcmZQzfC6UbfCVZCE`2!Evck6~sqCxeGpUTu${Vvod>d=F#~1kO#ILZJnUDch9S@p=Rh tU$WTWHUIA7wSC_T)s@971q+YNcDm2F)ZVd1>8{FB?K`V)Xh8Ml0|4cIItc&( literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00004.chunk b/nix/leios-mvd/immdb-node/immutable/00004.chunk new file mode 100644 index 0000000000000000000000000000000000000000..a5e1addf78e69e024d44baffc5dca1377eb7fd99 GIT binary patch literal 855 zcmV-d1E~Ch2Ze%)3K*1FAc~*eqpgniaVH}ec@c5Mn?m0Kr9VM@BHbjVE8MHtC|DqC z6HasO4AM_%$e`^A{UqJrys9=uW3M!Tr6>1Ebu779AgvphkV?^=aD$>3@;F|J5sCf< zMnUB$fYs5~fT~3}n1Wb9+aAS+-3?}9j{t~*Uu2ZA6bDvE1S;gud-E5T@Ki#2{T9yx zjJf#T*cz&CfveS&-3ID);Ja1b#WTE!F{K^}SWr+qYGnEpPx?!%`JTs1 zcjK7j&jkcnASqWJ7Vv>^n>-jVayFbShG(*KtA6j1A@q}0)+jg5sZO!z(I!_oqB;UiD# zbi`&?#tK=m8rJ@gxh;b;I5iX_@XMMu7B+(ulM;WnK3s1qv7^5Wf(ip!0l=CyNCy7Q z4Rm=DmlJbdPtzD40HH=goGtSo!TqtH8$^r0FB?xV7npZTsm zaD4aDwhn2FW^1xfC14{;R(!S=-n>WJilFgW9Y7t==*^ zZXLAaQyVYy9QX6Vj6{u5)LafPb=&S}?4z)@6p%9;L#*XCR;E$5f4&4x302Lyab)=_ z2HA@?Knzj>tU|x=f3)_@%=?7E(}-!Dz9N(SlwmKRWQppklXDO~pQKs-eK6^Acy*kl zYU$!tb8raolO8{uU%D7qcAcftl&H-{Rrl06?YE(Hu$&eN0eO_%-L&9V1EPs(m5(Wv z#mn49xY<#Nh){Xt*}V*Z2>O8S@yzRm9^g0M>$n1UGjGCFs+$c$&finbYLCMb2Orq$ zsNK)9$L*#3#1d2$Uvr)S?shyW+ua$s(dkhTnU<3mpFR(s#~$29S7&JW9udd>-S2hY zCRVfYBv%okX14Ta9`sfStP?)7R`uv*`&_#|$a$dXr$^+y#wvK{E{}Q9mjx@P@frYE hkr#Z|ST?Qy>;f+q7meL;wJ*J$X7YErqZ)vKpnz{5rX~OY literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00004.primary b/nix/leios-mvd/immdb-node/immutable/00004.primary new file mode 100644 index 0000000000000000000000000000000000000000..6ca64bb570602f1da322daa4097ae55aabce05d4 GIT binary patch literal 129 PcmZQ%7&u@7wAumy0#X2S literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00004.secondary b/nix/leios-mvd/immdb-node/immutable/00004.secondary new file mode 100644 index 0000000000000000000000000000000000000000..012a2813823b3871b2ed19c28c2bd423c55fefab GIT binary patch literal 56 zcmZQzfC6UbfJt#&OE(<4Tm0|u)0c-uT@NXKll#qheTnqHW7Es$d^FO`cgef}RXqg& DJz5oE literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00005.chunk b/nix/leios-mvd/immdb-node/immutable/00005.chunk new file mode 100644 index 0000000000000000000000000000000000000000..90e8154d3f04a2d210742f7ef77c35a52ac68550 GIT binary patch literal 1710 zcmV;f22uHf2Ze%)3mBqUAh5#SbN>D1>BAL8!Xfq^`vKRa8~(1Ebu779AgvphkV?^=aD$>3@;F|J5sCf< zMnUB$fYs5~fT~3}n1Wb94)(^~MUC$9Sc%~b{hTO4E&27{K3@bA>8OR_keniC2Pz!J zYTX~l%lPPl+~m!Byaat##~RfMh{t)HsccE}SWv|Xz82qcZJH*2itY`miC@+im)c@M z^dV^3bt9P}M(ST}r@=gyqdG!}C7W>!@0PIE4Y1y1i99(&a`Nc&Wl}VSGOCb3h~Pov z^0;~|pauk3ASqWJ7Vv>^n>-jVayFbShG(*KtA6j1A@q}0)+jg5sZO!z(I!_oqB;UiD# zbi`&?#tK=m8rJ@gxh;b;I5iX_@XMMu7B+(ulM;WnK3s1qv7^5Wf(ip!0l+Jj1OP~o z<;b>kVdl||XYH`J)Ifcn4CV?e&WJilFgW9Y7t==*^ zZXLAaQyVYy9QX6Vj6{u5)LafPb=&S}?4z)@6p%9;L#*XCR;E$5f4&4x302Lyab)=_ z2HA@?Knzj>tU|x=f3)_@%=?7E(}-!Dz9N(SlwmKRWQppklXDO~pQKs-eK6^Acy*kl zYU$!tb8raolO8{uU%D7qcAcftl&H-{Rrl06?YE(Hu$&eN0eO_%-L&9V1EPs(m5(Wv z#mn49xY<#Nh){Xt*}V*Z2>O8S@yzRm9^g0M>$n1UGjGCFs+$c$&finbYLCMb2Orq$ zsNK)9$L*#3#1d2$Uvr)S?shyW+ua$s(dkhTnU<3mpFR(s#~$29S7&JW9udd>-S2hY zCRVfYBv%okX14Ta9`sfStP?)7R`uv*`&_#|$a$dXr$^+y#wvK{E{}Q9mjx@P@frYE zkr#Z|ST?Qy>;f+q7meL;wJ*J$X7YErqZ)vKpn!r0g@TF<7_(R)U&UPNsU5Fr4}AT= zh+DXSz#dW=ZBqe`9i=5DqHf_@SRjzcRB*4CGfK9@ln|7~g;7>1(pXx2eri~x84QNd z;on#wem7TAet;78b{ZUa!Man#l&LKU6|NF)^68pt@k>Tsf>=Q4VUsY^RjQNel2&Fj zX%8a>QzNq~i;z7w%BZ0KbLrhtPScQB_;|(Z1=)plI}fthpLsr|u7cD$_HG?Ei$@h$ zP>m-Dok|`!@ZNFnY31-nur_U&y@H26W?>%rK1#N~x5sA<*R$K)F-`dMH+}zrP*^0q zIYnUtCV`ew@&semr!;qZ^kd>6$Fln#_NtD~2LxCkDOVj9@PTlfJV<32Uig|%K9LU;NB@|K+5NPQuw#eBLEg)eKe=5X0o@o)|aOkjISxdHS!_Z^bwA<_BP% z7M3wvVx#?H`+Nw33IkaIz}DLd3d>x1VgxK#Ib&{JggqXNP8Ng^;H^M6a2uOQ;hP(m zs(kY5oEPza=0-EvWt*FdRfM^Vb2O_9|8$e(5AXr1ZXeS)n(&bYiA+dzVOP(%&8qK% zR7AExVbiQ@zgi^y!Xl=Cm{1>>A0hb6%a;!-feqWsi{%f)!2bofExEkYV7a7Wr$YB< zky~>O37g!!s1BrD;!y!0EQv0e#u=}2vC8*bY&f1oPM)o?Njzr&@UFBUQR0SN~sL6J233b5};J!9|r6D z1x=H3LWmPt?O5NH^@VW><<0a3ZX!eFYyCQ97yDQ|25y_mQ9|^Ww%teXHS={-Ie>tm EfG0~#fdBvi literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00005.primary b/nix/leios-mvd/immdb-node/immutable/00005.primary new file mode 100644 index 0000000000000000000000000000000000000000..109ab6cb9c3441b49a50a6b0ba6cc4a3e7296e84 GIT binary patch literal 129 QcmZQ%ARkx&wNi=;0E-F)DgXcg literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00005.secondary b/nix/leios-mvd/immdb-node/immutable/00005.secondary new file mode 100644 index 0000000000000000000000000000000000000000..e48e95f5188c230708023c47032964e3543d61e0 GIT binary patch literal 112 zcmZQzfC6Ubfc;#ruEZaWd9_k@eI|d+-vb@dJL(U}1xe-xGxo_YRaIS-_b>{odJ%+X y4rc)BdvWe?_QJK6x>`%?1(ypnZ3Y0uiX(^s literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00006.chunk b/nix/leios-mvd/immdb-node/immutable/00006.chunk new file mode 100644 index 0000000000000000000000000000000000000000..205ba0688985a3cd7f53e2ec745a31179a4916c6 GIT binary patch literal 2565 zcmeIz`9IT*0|0Q>Y(sL?EW#2wN_=CO`)IDjmbHCQ7$HY^jO58J6%ukSS8^nK97&Ez zks~FNJ7LZ}4{c*^Ve9$!`u+poAHF|4KYag)_v;-GPK-}J1aATmPpeVtYUMFv{M75( zMh&XS__}>9dqsBnqh5hhCtCs(K&1EJf@^cNY#TeX#Im{*v3S)Xz&SG74=6h(a`(&J z41kE%C0vS*mDs*1eLVbKi(^+-r8?wjjYQ!3a-QGX1Z6Hn1W6Qc~YivFHK3kLSzV0bTbEjvGhC6&Dq#Uv#S{%_Qet~ z365~aoJiNGnV2omd~)PK_V#1B@hXHRQ&U&~K&TRAVeGizd_!w5xI6eZ}`x`Zj-;i>uJUoEuXO*Jl z32WsbT%)*c`cHb<1N)8%TqI2iH!6ac5bIoAE`sZhr1zxqMC{d$26gMM{|R<4gysCp z#iNwtu^$PE7vgu~ZO>o_mil*W20Z>8$o&v-Rbg&XWIGNeM~;dqSNNj`)r%_$ZyIa4 zW&FuBTFfIgS2#|sf(rtJnjIn6PFxT<;A8Vr0_BJG^4J-mBs=R+B4MDppR$^OJKtzV z9Ioe`!+6)DI^>*ut; zt-z8D{U{F)$FENL?FP0@F`r>> zyy-<=!!6G!2g@)wyO7qEpjTzItVIZ|YZB|}GRss!l^>khI^Oav=aSnXA+IkDTCF*@ zr*GjJsrmA(H%a;(gh*8o)<=hvf;6-$DyuQbo$Sy10TW#>Bi)4Z=fQoQQF92v8$WsO zo~Vxgcol$P;@U&KWZep)>pfYH+n2s*z@E6;tF78rio7t;WcEoEDc^qU3w|YOV0|Nr>LBd z0^(46H$pvxY4icoD>Mad`%qkAc1Y5sdE=o^)%VrnF|vHR;*(8iCS8tvz}y8eAatI7 zz}d-((K@*im#XyTM`b(-LN?CeahVj5j=ZIE1{gemu~ag18qb=CJ-lNIB0JRj=>`3y z(Y_6*WGoG}nRm)W;fzM_HZ`*PY9c`YG*-7}TzF=TLFYSC#@Zt zRV9n!T^p|mXKhilEi0@KqLzH^-g#*iUKIxr{*v}2mdKF9^$*1?2uE>xrj??D_N>*8 zEmz*L2|Ggt5Y;ld>9&J~!3iZ&>w2z9;z?YPr5Rl%c64womV(wJ|9h*9rOd9Q4|y5n z+u$Q5PQzapU||cQ(C!~9IR-i zt96A4V7Ooh_ef`{ZKHwKuQHS$4X5VliT5tKSQP2)_WU`To7qaNt#X($#fskHa#vc# zsBShXHOJt^4gQShw~lCwkA_D_{@3+~4xswI6DN6Dc~TBA588%-h&8 zueSU8_V2V0-}fzetB`q+Mbs$1mh_#HNfI-9Qs%^s(p(O?6;@E@w>*ED6bxZ!%9#|n zwZI8C3(JSHp7&c`-Wfr$nx2NfD1bqEBeJHZU(MqAOOkxE(^Rv&KTV;VC$RVLV7j*jBnluj~Ln?9{(5e2(i%dOL(> z4rc)BTe;|SRl?u?1DsRV$XYUfyuQ5r?bn@C-Ija&seO^@b1>C-Zmb|w-);!awhp9k t|2d;O9_OQ7P6y2m+`5yeyGFHWQI)>ZpHAa{f$uh1O#Cf1-3+R44*-%rI`aSk literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00007.chunk b/nix/leios-mvd/immdb-node/immutable/00007.chunk new file mode 100644 index 0000000000000000000000000000000000000000..dcb034716bd0fc378c1400ba862477eb470e656e GIT binary patch literal 855 zcmV-d1E~Ch2Ze%)5E$NAAV|+!M9Wg0QMI`Yi+m+=qIxeP{E0LEQSP!hk^35#Hdr8Q z6HasO4AM_%$e`^A{UqJrys9=uW3M!Tr6>1Ebu779AgvphkV?^=aD$>3@;F|J5sCf< zMnUB$fYs5~fT~3}n1Wb973h7{1eZoTi`NKi2aUB#8-1E}iaHDd2EZ$A`09r1-SWt4)v5x5pJ&w}wg9Nd~*6eCgx!FJ5 zq?}Q4t22ySAvx{wv6+onTnvhi&32h8)B7Py1k7>H%^d!JVEd2|wuB15!8%*3)c#y+ zxs2Qv9{>bcASqWJ7Vv>^n>-jVayFbShG(*KtA6j1A@q}0)+jg5sZO!z(I!_oqB;UiD# zbi`&?#tK=m8rJ@gxh;b;I5iX_@XMMu7B+(ulM;WnK3s1qv7^5Wf(ip!0l)zdupS5N zbzS?}SU=??H5x9s#hA%G;_pI|kA%%;y|3fOL2)r6dS-Ir+`a6&MJX%g2+&7;i!=0j z>-{||2?%M6W^1xfC14{;R(!S=-n>WJilFgW9Y7t==*^ zZXLAaQyVYy9QX6Vj6{u5)LafPb=&S}?4z)@6p%9;L#*XCR;E$5f4&4x302Lyab)=_ z2HA@?Knzj>tU|x=f3)_@%=?7E(}-!Dz9N(SlwmKRWQppklXDO~pQKs-eK6^Acy*kl zYU$!tb8raolO8{uU%D7qcAcftl&H-{Rrl06?YE(Hu$&eN0eO_%-L&9V1EPs(m5(Wv z#mn49xY<#Nh){Xt*}V*Z2>O8S@yzRm9^g0M>$n1UGjGCFs+$c$&finbYLCMb2Orq$ zsNK)9$L*#3#1d2$Uvr)S?shyW+ua$s(dkhTnU<3mpFR(s#~$29S7&JW9udd>-S2hY zCRVfYBv%okX14Ta9`sfStP?)7R`uv*`&_#|$a$dXr$^+y#wvK{E{}Q9mjx@P@frYE hkr#Z|ST?Qy>;f+q7meL;wJ*J$X7YErqZ)vKpn$8mrbz$* literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00007.primary b/nix/leios-mvd/immdb-node/immutable/00007.primary new file mode 100644 index 0000000000000000000000000000000000000000..c8b6673f19e394d6bd1298c193e80b6992ac3f74 GIT binary patch literal 129 PcmZQ%ARkx&wNi`$iqZq} literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00007.secondary b/nix/leios-mvd/immdb-node/immutable/00007.secondary new file mode 100644 index 0000000000000000000000000000000000000000..64dda915a3db165f283d0e04badb352474887289 GIT binary patch literal 56 zcmZQzfC6Ub0G@THOu35e>YhwY`15sH(4PPESxhDB;tyFaTk%8e@-+Tq=QC2Es_y{+ D@3#}2 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00008.chunk b/nix/leios-mvd/immdb-node/immutable/00008.chunk new file mode 100644 index 0000000000000000000000000000000000000000..b28ee948c7e9e973790405fc84c9050f9131f223 GIT binary patch literal 855 zcmV-d1E~Ch2Ze%)5g7MaAPRCme&ms0{Pm_%y#JpBH5h(h!a1g>_!iTa55~`EWLO|; z6HasO4AM_%$e`^A{UqJrys9=uW3M!Tr6>1Ebu779AgvphkV?^=aD$>3@;F|J5sCf< zMnUB$fYs5~fT~3}n1Wb9t=@=LK=?1*Obl1_&D7W5oRMw&8!Ppn|36Pq79m)MPnujK z+Ku$-R!1Lmi~bIsfNo-++N;*lufD{>SF8uLSWs_=c>Q|gh)cXP{+(V*mQKz_XV{68 zOnMR;c3J;PF}wm-K@10^jMRo#=anUc-#;R|4S6Pn96L{GKA}C?dxr^ikarc*i%pId z@Wz`Reg*_sASqWJ7Vv>^n>-jVayFbShG(*KtA6j1A@q}0)+jg5sZO!z(I!_oqB;UiD# zbi`&?#tK=m8rJ@gxh;b;I5iX_@XMMu7B+(ulM;WnK3s1qv7^5Wf(ip!0l?A^x}#i* zKNlPbW`t~&3Vi3q>h~^6uofLcy~PL957mGD`lVkNWp0j~qoBG5prkGN1BkgkxINIz z3?X_tI|^xwW^1xfC14{;R(!S=-n>WJilFgW9Y7t==*^ zZXLAaQyVYy9QX6Vj6{u5)LafPb=&S}?4z)@6p%9;L#*XCR;E$5f4&4x302Lyab)=_ z2HA@?Knzj>tU|x=f3)_@%=?7E(}-!Dz9N(SlwmKRWQppklXDO~pQKs-eK6^Acy*kl zYU$!tb8raolO8{uU%D7qcAcftl&H-{Rrl06?YE(Hu$&eN0eO_%-L&9V1EPs(m5(Wv z#mn49xY<#Nh){Xt*}V*Z2>O8S@yzRm9^g0M>$n1UGjGCFs+$c$&finbYLCMb2Orq$ zsNK)9$L*#3#1d2$Uvr)S?shyW+ua$s(dkhTnU<3mpFR(s#~$29S7&JW9udd>-S2hY zCRVfYBv%okX14Ta9`sfStP?)7R`uv*`&_#|$a$dXr$^+y#wvK{E{}Q9mjx@P@frYE hkr#Z|ST?Qy>;f+q7meL;wJ*J$X7YErqZ)vKpn$OKq3Qqt literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00008.primary b/nix/leios-mvd/immdb-node/immutable/00008.primary new file mode 100644 index 0000000000000000000000000000000000000000..6e677301ffd491e8c4769d7f2d04f7e490c72301 GIT binary patch literal 129 QcmZQ%AP!gnmC*zP0OM)}3IG5A literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00008.secondary b/nix/leios-mvd/immdb-node/immutable/00008.secondary new file mode 100644 index 0000000000000000000000000000000000000000..9c60085f24320f3d9d8c9309308b319548e06f21 GIT binary patch literal 56 zcmZQzfC6Ub09nrqNv$_zr%rGcJp24Z+avD27iJB2OGMpnEV#B@)Z8HS{jHNw)!za4 C5)>i; literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00009.chunk b/nix/leios-mvd/immdb-node/immutable/00009.chunk new file mode 100644 index 0000000000000000000000000000000000000000..7dec69aef1dc29aa0a0c75450ff013f03774901c GIT binary patch literal 856 zcmV-e1E>6g2Ze%)5*Yy)SRjSi9hHzp5zXiDhT;p3=r(}ebQMO}pw_1qH!xN2+R0cT zYZFd$?F`aSXvm=L2>m48-@K|eMPsitfTbt*Np&o_SRkz%myk-)op6Jq7xFk>i4lqZ z1x7*TD1g<`)_|%-IGBQ1Kpv)_h;Rs#{tr^_M)-Ba?&`N8O1t^o{>Cx_8m6!+C8tdm zInW_IE?ZoF$n$NA9AKJ$AFCc4rxtM@;#h4-yI4>jqOL4$^F*%!bqZSsR)$s*F=2n* zZGANLIu7~z4DYE=wLGR^w*ZX_#EgNUyarBGd@K!Q-r}~Z$z+C+~K+KYe zgt&7+iRS|ZSRg4^9TxC`aGN|xWf))wd+Yf$3cEkY6Es7`Paj%d-0_51Al!X77~y%` z^eH8?@BmmV(bct({zxdh^|x|Zh20Bh761TPKoHkqp*vOy291q{Ell`5U6|rSH=oiuo~9>kGU;_GdMLABk;?bHWoI66O$5uwmw{MDzT%#3xWy*SpmS>k+L!P znAjH=66$;~*9>L++A&^BXSV_<(o1cS`rKiyYw=!HBtWI(SL8Aph5s2KNHQs_7Xi<~ zhD6m)a;5-ji)L%GPbFX@N>+Tf7T&x^+KQm@SRSrkxK;;3MhSld^uE!Qd}h&yoUPt6 zI&K}b<5L?i^Bni{!Hh(WQPf-xFLm4QXzZh~wiJ*v8$+z+Hddxlwtv0^P6<`bx^ZOr zDhAn$Hb4wg0<1#6@PD-S%*^|Qz|)9noW3HH{FGrYpk#^as*`gNJ)fjm{(Ug%a(H!| zq-yEnRda9%@RJ@toL{;aS9YDH(v+ypMpgIJIqkQhbg-Nj2?2SO+}*U`Rs*7mX_b#D zmBq{4MY!2fh=@>m!{t&vd8VE{KOJe6<>3n0Pc1?Dcju{xY6lR5Sf;f7oR>4p2r^CMptKO_#P3*{@w3& z-X>PF@g!Ffp=P%9XCCxc2&@x6vsU%!W&2#aKFE2X=%+{Iy~Zkd=Pr+V(U%1)rtum8 iSCJQd*H|{K|Lg)U78i}(aJ4VJoo4cPxuY6@fS`axC!nVQ literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00009.primary b/nix/leios-mvd/immdb-node/immutable/00009.primary new file mode 100644 index 0000000000000000000000000000000000000000..35ef5387f67a386bdd2efd0fec1be335fbd26bd6 GIT binary patch literal 129 QcmZQ%ARSl$wNMQM0IQ+|VgLXD literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00009.secondary b/nix/leios-mvd/immdb-node/immutable/00009.secondary new file mode 100644 index 0000000000000000000000000000000000000000..9d0bf59bae0859a285f31c0f0c1b2345420eed85 GIT binary patch literal 56 zcmZQzfC6Ubz@=InO4hr@zgyMKwj}FB@SesGvHEIj?0!+{!y;=4Em_ zhBGfaxpp{to!q>Kh>06>S;lZeB=_9^a6k0Jeg20}k~%Xf4Qix{0uX|8fh+uUHD2T& z#1_VCfZg#Lm)(?j77CkbIwK3gNB~4m4=GxZfBJ&3i>1rzW_tNpj{tu3gh+sAq;+pt zItw5YFusI@ME%WMM~q`Tnu#J-l?~)@ojzqBp4V);9 z$q-Pz->ogV_TE9{*yz~$rxeC6N7XYAXB$F50K(eW1h&eE<~ZZR4TIFmV80lD_l>ov!wMaHCCA%V+%DCnzl>{ z9eI+(zT))TN*)!xB~ltF$S3cBP$2%R(xQf&`LMlC{GzR6=!}j1Mxi+${c!zr`>7RJ zs&gbi!%U7wO&o~NJuF+=p^cR*I9z8wN}Tsj9y=V|Ifq+2VH_|WxlL)CR#f1xJ?%w@ zk>s-lH43NK%WWfH`0Bh8{r64cnZ!hHV$#2_42)FW0R(ux z$pZd2a(?a>c4Es|gA?qa^6IcwXI&hC_uwo>P?#$F zqNuj=IXQEs4lQ+PHIcpE>If^yn#Y02M=04(_i$^ZZW literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00010.secondary b/nix/leios-mvd/immdb-node/immutable/00010.secondary new file mode 100644 index 0000000000000000000000000000000000000000..20b628ca466ba81e70ddee67ba750c51d86eaa9d GIT binary patch literal 112 zcmZQzfC6UbKu({N3t2zy^wDBbU#!E(7But!o_=NdVu^U`+sBrqDtB={-uN7%n$ZA4 zGeql^u%-p}{5PSQ1NT?AE7StoO literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00011.chunk b/nix/leios-mvd/immdb-node/immutable/00011.chunk new file mode 100644 index 0000000000000000000000000000000000000000..748e7d1411dae14c2f4d142ac964b5dd5fab8550 GIT binary patch literal 2568 zcmeIx`9ISS0|0R3*hH92kvr*{Gm$OB2N_H5GC5PDC1fGWP|hi&m6ZEzj!9*d zv&1HvBy&tyj_Lb+U(f6H{QUgzyk5`q!}ISG>+zYOmo{hS zC<6C&O;h%*1TlURuTsb2=EP|l04%E)6<(cZ0ITjs+x7~) z{POyC-XUz!`epBq)YfU#QKzfuEXzt%7;Y~=0Mm4rhpyZVFR--tKj15LePPpBxb;M@ zq_I_xv!W+@lAQ#==malL!u35=FSP2R&&l;@S$OQ$3HT@>$owQ2TN~BI!vmZg&?vq$ zZm*6-HApyQ{h2LGKif5q!ZFlPqatn)@owgP@d2}utlkWsxUK3@Y>(OMcOl;*XzpRJ z3y--MwsD|D;XNL_9p6+HCU$k$MjE+0{Gz~|AO28%%U6v)y@s*+9auNoSE zS%MNQL&)jM^CkwL_~Nsrm_<%3j6GXh&U-TCcNk@oRe`wN z{@&ywYJN&R{2*(MYGVIXpstKTWP%vf38bIbSC+<+@*SOZxt1@v=X?g;^J$sjDub~t z3oA6vphhnsQnnL>X;$8AVG|pP)i-+bvZ2_n32zaWb z$09J5vz~kfJlnq}5TboT%{K4RXGYc34EEfP^GiA~22tjfCjkN{Yyc7SCu~1 zMmDwat2V}$t8-3A>ofzfs)Ko14ueJEw;oBanxhF4gk1sKQ?nZQ(ZMl1*~a|AKVCId z(qe8~2gbE?0EaxOEbSLH;PlQq8N2)wzqoJZ@35{P&8KN2$`va&e%8`GsOl50#+518 zBza!BBA>r0%`X8E{ETO8ubq)2I&HD#gN@yw+ZeT^{KJW_@ayj+Bs4p>n?EL&YkWtn_#>n<8eDNg~j~A zX#t@%&T76Y4sN&xD5K5p%N-IMPFhW%Ma2d$pZnz~gW8*aSjKMQv4Z@F@DQ%i6>&Ge+m zIlkv`%F2zp4H|7bsbe@bxbU@d_6`xFPr69>NzRTGKUPxau^VqNA8|Fhuq0K<} zp+ZnnK9R*dOEH$36LguT!FiC4fKLvFQfRd1zVQK{hl=L6JT2P zhsCE4mCm4t*Xy?z1+2z4KbHO1D`^>Ce*pG_Rxq~_xZf=+G{q--vrGS1gp+#x*V}_F_kdZ-Qvy?p^z=? zSNxXel7GgD1#db2s@%Q5XO)?2@_LhorRv{3OLcZeD6Ey9KEdna+=Avs;-4(yIt4rb zvAQ`v)o8eS@mj+wSBn`<5e_Wz;!lOXwH=gqd3|7F`MC~DrTy1Z?q1+rSTk8h#>Q*O z(&vhEHf_s#^GWCTmsp1zS^He{Hb0x!_pasPqW{ZUd)7w;tbb!Qd(-l1RqLv6x$xOP zY7+W-t?78u<{3FR7AiNTY!`jFChTKrWz^b`DcP&eUt87iUHVLECtGiC ztFF%v+b4%FF%>;j_J37!BrW_HSL6n%YybLp>NXo&n2IQWI6ccu%&b{>vQYgtyO?~f zjf?klH*qmXG9LJKlS^;UgX6yIe1oe$2t`EvaG1y+#g>?Kae*BByP)Ka*(o&#?Ui@? zxUXJ1iBDmYbKL~7Za%h_wLuNvy=d8VFWR)ko<#DjI{%4u*pAYu9^afsu;nOd@{VwCp;tktG zCKyXQuX$<~wk&X4{XP~y&d{^F3R8Y+vEA%8bKnVLTI00;L;aR-XU_a?IdHinbIv}c z$$zFK>Muy?e6?zFv4HLTC6WJX4PF*il+Ia__3}|@aRJAN$#V8{;&(}em(5*zY08ST zZlT|=Siar9uw=s=F;2$HDR=H}c@W0Ds55hFzvk4Vr|-D#xEa{d5m5Q$=3bt9j$aLL zKc0ErD)+$r{_7n~<;MAkLRQV@bvk!H_-t1HVIg+;8?RT~J-_Mr+ogYw2!)8o7tdpO zS7xJm`>y1Ui!TEOW=@+dKHrXi-f_7*ZsF+}KjZ|D|GWFX^qyMS=8r1jf(z5OeMy)5 z62`Gc*lu&!*B7b3V|Lq}s9f-3x%-p7$FwS*>-AS&oX)Df?4uMz_(buV>k(#a|G#0< z7ZdNjTd-As@7%OccnrKchpLX zWSu+VGH>esZK5u6RLWR~jLlZfpLt3CpOe;#2_7W}zTXzL(o5I>IgkCH$-~D|Hwu|; zf?sjwF*u(V{=#drT65j~#c~ZH3%Oqx{@Yva%3u%?U=bV>yLQ{Lxq*6;ruBzi7T&Qn zW?i>!`pGLNqpop9%<&0gKeQ(EX!EH@!gde$W*R^KAox#!UEnkSg?|NchH87am;Bxx zGMPiht9R;GFAvrGgDzto26(BX^ORvnV}P<<5uTMs8| literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00013.chunk b/nix/leios-mvd/immdb-node/immutable/00013.chunk new file mode 100644 index 0000000000000000000000000000000000000000..02a7f83178263ca494e13eba15e01b3c3ef6b189 GIT binary patch literal 1714 zcmZo-Z*A(5kdkEVh)`JBRiEJa^~plc>5JWZw)UJ|bltT@toQA?HWt0blgry|A{4TP z{fgi6T=LI2vEVJoUzNM}_pCB=Oy7Mr_pUVnPd$|r`BBJVdb4KnyQ;WFhpoyyt;M5KM#%FU$+-UwBF@T7h_wSWCPb(@VXOhuGGoStPSX4Wh`S*U)ST}-~# z#>M-&o4A-G84qNztgW2Kd;a>`dKJ?dPrUZ7i;Iu&woW!zHaITrUX)PwT5!RpQ`rlf zUOeBdr*~}s-YxH^)|9z^?x~KOexTLYk~OnCEqjx{YJ##?Sj{%Edwbk(buIW9A-67W zM;N=48)rT9mwgwf)TCW(pR@L!kyW1TmdC-;`k!UKe?Hjb(i?ashEKor_PdNXi#Kc& znP4pKyymG{*s{QF_4`=-I783wDopvQ#dfpX%z-C}X^qqV5A|EVojLQn<-p~R%sKm% zCjXg|sJ|ek^VO=!#R9hTmqh-nHF#N6Q95Ty*2_ns#RVK6Cd=8+iQgp=UN(2>r70`U zx`lqfV)=Ia!jcVh#5fr%r`)-_%H}l^f?D3RyLq*Xi8-;Imo%hlSYXZ@gY{_xz^gZ>;Srt(mG4|E)zGk@p$VL^q$L@9BNVnDy3eC}K2>AgB=d=ZPM(=1M?Ta@ zU5vFZP5xCfao7FLRLWR=)3+Y^@xQet*r#L3dCjn%-3vlmzKIrEm8W(V7QCkciMEPu1$mxb@5y&3sZ zjf>p`E6*_+vtN7hA@ZdCiH%VY_nnx{-CUUPX6sfah2)41Gm`=h6N{J3d%QRU_BJuy zKV^OP$C`VKYeJT?47QBr{rkjPKas52H@B>CJUsJ<^4up`NjELi%MI`4RV@u}TCBzP p;j#7X^GjYgt1dmXr$}A9$>rs`<(Xym4tYO%-)tGpSc4#A0RV4nNs<5n literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00013.primary b/nix/leios-mvd/immdb-node/immutable/00013.primary new file mode 100644 index 0000000000000000000000000000000000000000..52b97f69881ba577056575d22fb11f8a06ea8e07 GIT binary patch literal 129 UcmZQ%zyuaRA#_{-6r%|S05oU|DgXcg literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00013.secondary b/nix/leios-mvd/immdb-node/immutable/00013.secondary new file mode 100644 index 0000000000000000000000000000000000000000..6c6948284134921e7e13a0d81409fbb397c52579 GIT binary patch literal 112 zcmZQzfC6UbpnBQt*zJez^QfLr)mS&ld}5%JXJ*Nf4>eL3W35Y*f0az!b$>HNHDd>a yW{zY4>XXSd?+ub~)?s9K&O4}E{7|}U5u3FAQo~nwK5S24Qy=8hnmHA!uNMG!cOwM= literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00014.chunk b/nix/leios-mvd/immdb-node/immutable/00014.chunk new file mode 100644 index 0000000000000000000000000000000000000000..7301adec21af37723e0d0fde3415cc6f66bf149b GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7#tY^yjUPoAA>9b2SaYbEpy=;ilPP^KczA1-0-(&tbbBWg=v*o zAZrs&bL|Y$PiV-X?FjuO-QT>bHbrBvG=QZi_epguxmX~r8<&tu(VcLEq8IWwUWpNj z{sl%s8{p)yKT;GOMg%U1whLu=u#0}oE2HL zanvBAl3!3uUW!K_>;a{s2WaC1MZ?40I7r~}Lcmy1QNSTFKbeD%<+O!T&#um6lFzRI zpsE2-TA5|PcCW}p!BULU!WU~0I|S1FU$t0NQ1l_AwynZ}_P48f+J_ME8SgZ&&Nm!+ zVoevl8L18i1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmYeHyGi0 z-1I3Wv+w{|E78@pkp4(0yY;tnScTmSXBGeeSU?chVWB%#2?mXgg)L0@J>>}vS+E+`{*SpWgEKfa6eIAq4i#9+EQUa_(zwm#w_RP%tguv5?X`H?yll+unFQ8Z+4-5IvuyS^j-6>2i2= zoTO^$;#G5S2=J30Kb&8>7*}?krP7qB%|=!C)H&_9p>(jE76}1)l-%94;8p{oiD{LO zDV4>`+(o$AQHY38dF0u>41WmvfbH?j>xCZRH{a{H0(UcS!c?l84MNV}Q_X6R!x9G{ z*z2g>&$7qurToMaR25%yo&fH4JSp4V8Mx8uQ4pDylNX;p51z*!+(uVtX!srx$Nt^# zb>1dcv+*QX5us+b^k*LQRtT&UKC@Q!=wLlI zsVxW6&WsOGaISSU{)dJ(D!c(MQTk?2FY1tp;f(;j(e;t@qnv^x9=?HaeGG zInr^=o?JA5S>}uef{qAu^2g5*r*bPy^nQQ&+;vz`-A{+nkv+BlCdUi_FJ5q@da{o1 zKaamJ`Qy97hVCFS8xf_2PsHn^5jl>_Ak#q6t86=UtEL%){xv;^X0CR~^FK3lAh^@t zCRo>^aW&))1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmbrTlao@ z1H@ZiBqrE}wO$%Rcltj<)rn|0KnZWNbix1tSU}Dwo{HH>CvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d?OnW-|d&b}Th{h#^t8X%(H*9EXy=)dQJuA(=i zy)zEh`10Wo@BylBAJaIR@R0?HOh|NLSI@Z3s_%nTM7BX;)2wU1S|t6#BBp?tP#>5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs zB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQYf(M0yiWnXl0r^-UCm=OLAjM$`hP=eT z>WK4NR!QRarfaBFM(7|@LD-5Ew~m);%yqPF^D>nxf>JRt^rn?d?9d9n0+i&M($OnC za^K@vP=PRgCJg;LmbuAyB(aBxHyS^l<~Kao6BSbpU}hVl&`4qgOhz`qXb68ZaIfe3 z$O3X(U_a&s+)$ag8rD(m^NKfOLv`LcgJ4b%v9h)y3~bJ^7^e{(h017P7VI=@g_iGu1!;?BYqC!zU?WOae6|+eyhqxK zpz&B9u3orS2SP>(e*^Ts(Ug2<(TAL^-ZDCF9kk<98!z)5_w&JwM2%6@Tn;aF+wN%W zqp-FVkTV-YtmQUVrct(kz64GQRn59_Wcexv*^4$n3{nEDLcj2TwD!!*`-H&Lh-sX@ zB9r`-VK1O$iR!A8a}YhBq*?xbFzIr5b)2MX>Ecy$a0u{|9zUF4x)@h>ou$&0sLe)I z_tZJypmbDjY1c04KD-5I#i z=}{1wmXjBsJ`bM99^6J(XK45y5y$@B?{(fLRlvn$mhTH*Z(Xt+VT|6wI)`_t^}hn(;Y= yW{zY4>hmg2*u%uOwn?g^D=+=g>J;WZW|P>`SwD%s)SO$qI#}{hu}?Tu-%kKj@*?#B literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00017.chunk b/nix/leios-mvd/immdb-node/immutable/00017.chunk new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00017.primary b/nix/leios-mvd/immdb-node/immutable/00017.primary new file mode 100644 index 0000000000000000000000000000000000000000..48e4f424bac805f9bad4601a2e30e10c4393d1e0 GIT binary patch literal 129 LcmZQ%7+?SZ0RjL5 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00017.secondary b/nix/leios-mvd/immdb-node/immutable/00017.secondary new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00018.chunk b/nix/leios-mvd/immdb-node/immutable/00018.chunk new file mode 100644 index 0000000000000000000000000000000000000000..c2b08706b0c390c83cc80cb20b76ea17b3c7018b GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7#|q|E?6J}2Cae`h>C7!;;Uo>yf%^sX9e;V=_#Fat5X@mb4*uQ zAdtsYaIcp$O18t45R}D*QC2C^SXz93YFMNh42IC*-&i1iH&;@AfD-n08XR}Qx>LlI zsVxW6&WsOGaISSU?k=IVJ{HkM!tINP}Kc6mh9**!=CvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d&yx;^$FMVLU7;~ZN8nCOR{k^6;VjJ7!=%MQnc@(W;RB1y&aTD-A zpSOf0e8W%*@BylBAJaIR@R0?HOh|NLSI@Z3s_%nTM7BX;)2wU1S|t6#BBp?tP#>5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQYWpkis literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00018.primary b/nix/leios-mvd/immdb-node/immutable/00018.primary new file mode 100644 index 0000000000000000000000000000000000000000..bb11205b29aa7489e57b025978c766e7f1fd44ad GIT binary patch literal 129 QcmZQ%pgynw8c8$;06k&?q5uE@ literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00018.secondary b/nix/leios-mvd/immdb-node/immutable/00018.secondary new file mode 100644 index 0000000000000000000000000000000000000000..d0a247f158f85ad9460869437416936f0a53dd4a GIT binary patch literal 56 zcmZQzfC6UbpxeuT#$<_$1cgN|FIf=sL+{CIrUsSlm7zEFmZfa77yNf;9_MO^Y9>7Z D-!2ji literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00019.chunk b/nix/leios-mvd/immdb-node/immutable/00019.chunk new file mode 100644 index 0000000000000000000000000000000000000000..0e5a7825468a768631578495c207e98b6fbd28e1 GIT binary patch literal 2571 zcmeIz>p#~_%VnW4 zm&hiSTXRXWkPAP_<{P`vnYnVgT`3+Iok8FnAu$x7D9WUM zn3@C-iDp>OM54ma8}Ng%ubaJCxt03T`)d@!m-z*uOJ^J}Bm*{%k8oGjmnZ>AR<(|r zR~x=Y4EvBvKB67*?JM#SQ~wuflZ57Eo=3-EC=VqOqd|%&*5Rrm^sZK-y{M|+ z9f%T~pUPUngQq`cu~{|&3dXC9cF5X#|K3GWYPjlp@WW+-Lb4Ur=w03~e(Z<9&aci(dIv9XLf6CFIf8Q3 zwYK-j%V_@O;YcNckcD)vlxUz#Fd}FqyZSaveO~CzJ?Rx0?>zw!pzQ0V~Py!uKAw!hAZ{X#u$s<8_=!BomYW4NFZC z)vrRfS~ydeIMn@r<~hxi;sgLp>dgxIrsz1oT& z1xI~&_~%jJ3c4b#EMb4Aw{bSC$~!gDTITNt%c&zUS=sH~TBFB`R}x>g zdcm~|pbXl#+!5QHeA_w&frprXg1N?)S~{~x$H+wNi7Okrl%(^L|A+N=fu*hpas?12 zZRxESm*cKxK@?{`LhJ~HVa&jUTA)=(KH{^v*`7)O5e9L?&&dqBUwKQOlit?kPPS4_ z9WK?H5X%m)osK!e01(wm`6L(iGJ725{{>)wTUC_k3_12`NMyWb;K<5 zPq_suLpBPhFRq=skg0qIg8Kkvf`a?o#Ikf_U(;I~w-w-QZ5uT7)C(c=z1l3@>w79c-sxfq4mmpj z;`W%CDgP8^MUFoO*V$*%#y|ph#JD3syad*-fo-_3aDCyrT!D>wYZOUZEM;M&UT zd-jCC4&MZDc$_RkrPm zNew@HdpGZN45ft>y;9HF$_+FmUrzr)&B4o^ctY{nNigC^-Ha)sgz~?7<0GXPb5u?i z`8OZH-gsO#nER~H(R*$9_*`R2G_42<7LCj0a2vj0#Ga;y}jd=PEX_`5tnQ9^}BDSnn7h)z3Vd|GOvGOHBbYZZH z5F=d$v98Cg&fqrBw^+Z8BhOSg@!H<#-u!Nm701q(&?{epi(v1=2%~^$^=|>l5DLrW TM!qy`dmOYJ%P58aHP$}?6@=~W literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00019.primary b/nix/leios-mvd/immdb-node/immutable/00019.primary new file mode 100644 index 0000000000000000000000000000000000000000..163f0d09a423fe93c53f58e074743b1059080819 GIT binary patch literal 129 VcmZQ%ARSl$wG`mND}ZuDV*r8K3n~Br literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00019.secondary b/nix/leios-mvd/immdb-node/immutable/00019.secondary new file mode 100644 index 0000000000000000000000000000000000000000..43a1b63d391141e75a1b9b26c7a64feb67383194 GIT binary patch literal 168 zcmZQzfC6UbAU_s1>G%Df@e`zv=~jDqbZ=g0H*eZ5)8}!&D-JFAv*G%ScjBiZs+n9M zG;<^aP+yH)e&xcwoqLi#Rp#^yOTM@!>|9fGCG7k?#YCIT=?b?j%=uPA^|?Z5woM>? thXkIjxnXrr?RHJ>30p<6>g0L9Ia$QY?cQeInJHYf<@o8}?>nISd;mJ~IeGv9 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00020.chunk b/nix/leios-mvd/immdb-node/immutable/00020.chunk new file mode 100644 index 0000000000000000000000000000000000000000..86dc1f03e6661ba866478c5779c44a44cc19f6e8 GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7$X@1T38_1I^HJRd~L`*Ar^aMp8E*|7I!}FY229;aLlI zsVxW6&WsOGaISSU_<<=y^TCvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQY&s3wP literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00020.primary b/nix/leios-mvd/immdb-node/immutable/00020.primary new file mode 100644 index 0000000000000000000000000000000000000000..9dffe10d00c85c8d44e3c0d8e1dba5b0573c54c7 GIT binary patch literal 129 PcmZQ%zyuaRA-Z7zQSk;M literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00020.secondary b/nix/leios-mvd/immdb-node/immutable/00020.secondary new file mode 100644 index 0000000000000000000000000000000000000000..6f9f4b5e3b60c7adb5ea549c69ba6edb5588ad08 GIT binary patch literal 56 zcmZQzfC6UbpitE|XUl%#Oe(cbE=h2&;iygcns+pny D`fL;$ literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00021.chunk b/nix/leios-mvd/immdb-node/immutable/00021.chunk new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00021.primary b/nix/leios-mvd/immdb-node/immutable/00021.primary new file mode 100644 index 0000000000000000000000000000000000000000..48e4f424bac805f9bad4601a2e30e10c4393d1e0 GIT binary patch literal 129 LcmZQ%7+?SZ0RjL5 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00021.secondary b/nix/leios-mvd/immdb-node/immutable/00021.secondary new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00022.chunk b/nix/leios-mvd/immdb-node/immutable/00022.chunk new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00022.primary b/nix/leios-mvd/immdb-node/immutable/00022.primary new file mode 100644 index 0000000000000000000000000000000000000000..48e4f424bac805f9bad4601a2e30e10c4393d1e0 GIT binary patch literal 129 LcmZQ%7+?SZ0RjL5 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00022.secondary b/nix/leios-mvd/immdb-node/immutable/00022.secondary new file mode 100644 index 0000000000..e69de29bb2 diff --git a/nix/leios-mvd/immdb-node/immutable/00023.chunk b/nix/leios-mvd/immdb-node/immutable/00023.chunk new file mode 100644 index 0000000000000000000000000000000000000000..4c3ed055d6f1551d7041e9be17deee713c86a5a5 GIT binary patch literal 1714 zcmV;j22J^b2Ze%)7$g}2!&o4wGTf{#QOR`06#BtuQ{FypBlV&}>*GL!+~VxHqd-eo zAdtsYaIcp$O18t45R}D*QC2C^SXz93YFMNh42IC*-&i1iH&;@AfD-n08XR}Qx>LlI zsVxW6&WsOGaISSU~oUoPE39e*!n)3ID{$w&wDos?_k~wGALD;QIQG_z3t_TtbNh{1|E`ezwUEL=$AQZUpwz?zhZ~kOpJlKW#%Esp?o0C9 zA;-#tV%p>i1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmbrTlao@ z1H@ZiBqrE}wO$%Rcltj<)rn|0KnZWNbix1tSU}Dwo{HH>CvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d7zPM6II!ssPkP#54YxtpW<76zn8UKUD>wG!6TZtk9TksP)p5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs zB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQYf(M0yiWnss0>)S%Ls@gn?FlAn zdVo$WceOrmz6`qY{{kt<#K|?crxuqWSRiW?PIK)H(obl}pzR3#B;DV=O-$=Y#+_+fJY zCoonBI%OIDs!@GS!o5M9aV*X^f_G(R8cwZPpp|GmChzqC%wNWvVS0Aj-by6%-WHOc z9)w?5P@PpGmqolssQSm>>!novhog`zfFQXf*JUah<0{jO$F3lCL;@Z0S~lJ%DStBx zZPD6iW~Mjd{*T3nU5dlkVf2h8S!8Q5iGdxq&^0BMV6YqC!zU?WOae6|+eyhqxK zpz&B9u3orS2SP>(e*^Ts(Ug2<(TAL^-ZDCF9kk<98!z)5_w&JwM2%6@Tn;aF+wN%W zqp-FVkTV-YtmQUVrct(kz64GQRn59_Wcexv*^4$n3{nEDLcj2TwD!!*`-H&Lh-sX@ zB9r`-VK1O$iR!A8a}YhBq*?xbFzIr5b)2MX>Ecy$a0u{|9zUF4x)@h>ou$&0sLe)I z_tZJypmbDjY1c04KD-5I#i z=}{1wmXjBsJ`bM99^6J(XK45y5y$@B?{(fLRo2~#+&2$(- yGeEE?$+FYFf`2TI?H4Luz>TeR4<+C$+61Nyc literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00024.chunk b/nix/leios-mvd/immdb-node/immutable/00024.chunk new file mode 100644 index 0000000000000000000000000000000000000000..53c872f6fc0aeaffdbbfea2bf63491b8196336e3 GIT binary patch literal 2571 zcmeIx`9ISS0|4-uYm;-!2(eI((p0V?ffoD3xracycp@jCrmfo?o9Ip4aPnet6#h!#iG-5`Rzr$N}(Y04dSm7O&|Oy6*n)v$5cOjg2?O~|x4 zH+bZkVVMc_O#cW5$4#!X@|sL?QBy5Iml@zy@B)PA4eX7rLOk)V?+`L+TgLuN5+N;~a9&38f z+n1I5&}WcaKFMb;ZetxDok-vdLz@7>6#+(&%6p@nl{8_hgI$;xez0kPv3%Fry77$H z`>N~hZtA<8s^xLn7?o_5LtFiQSyI|}B*yygPfIa7_Jo^snqR*6Y%cYxu-x=Zb0u<7__b(8R{U)R<#NZU?)P-jub~`aM$BnOz>*%fjsm{=UxO!6W z%MyZW8pwE{I;*ey2^^CyJ2k&e{7|-#TV%@6?aBBxOM2(k`OS`dROt#ka4V>ty-<$1 z+1jh`?L0f75u&)T&eFH56s|8Fr%ge|S!391?q3%)(PcZwek!$m$#nD>!sqm-K&y2> zZW~(>qIGMJ`w|siLA;t(_Zi!eh{32+6_wQ({mqQGyc?se+Gr24+;5`&%$P}}$jv=a z;-PAC&lLcIxziEmbI>D?Tz75JX~Xdy3Q#NDsA4 zg1asP6B$1#x1iGl>%u{*R@2vajeX>JfT>7OZZFnyJ*$y(c3FQd+zA~QR}>fjk60Q9 zz*7KnYQ{D$6DpbTLf-`9afkj(Y%7P6akZ{>ZtMij)o5`LKwgJmBrb{%U-Exbvcx1 z7E5J<5b{kd^+Jxjzfv(JE%an#dRq^>17%rpp{HRBEfD@i3buYB^E^Jvjy?uOuOS}P zDzF1O+qk9bMhSKV0RR(BYMYmII!JsNNJ$xJ$tXITss=~D`;1kplclMBs1^s?tDbIY zb-xPsL?{q;28Y+oO#_W3)1`U&kIGhDd{mL#RQ4};pQg1rF#ruZF7@xlV#gTDPe!uW zwGP*-BU*T`_)$Zatsg#cj4)<*haIzRL${nT8>wb*9JYNT`q!z^?lmGrz0pAL}S{dUCeL&ATfGt-XH6mVV{-; z2i*6)UVG`Vr^B!; z2xKK)**wpqMIIlKUp7p8G+^tp`2oH7oE}z_hky!1(%78(uQp{IAYoGHK7GH*qFVa?Q6fUUfqBZZ<)7x9XCS=g z5}9=Mp#M-Ta!wVO_w!kPEdySD7*pXMtVT`{jldLU=qzQ6eEfc&{@cX@ja?@e-qqJ= zUfc0iw&$qY8>V~j>mMa83al=D0OK!f!rdh4p>MKZbjCtOw9V5y9{)~KEY||}pTyuR zLAL==ffz26K4@N6=`ixgIbFZGs&h?wS^H37uF=?m5zw8mnmwL~qKTa}+WL@&(EnO2 za{(eWaalWF@|bYoIA(gdnPtd5hZex-6KoVjupHSv74=Q3NDodWU Wj@mq8-1#IWyLd+8|FQo2vHl8v4dOol literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00024.primary b/nix/leios-mvd/immdb-node/immutable/00024.primary new file mode 100644 index 0000000000000000000000000000000000000000..0f3c16924076bf4c56c31b31e6ee072d912f3c62 GIT binary patch literal 129 ZcmZQ%ARbr%m6C!Bfad!*ATt#2_~XHLNSBX0j}?|QEiOA&87yig?%s_zMeX4?eP uw@`IqIA48U!k)>&?kmLins1q6?sog>f(cRl?LWTfOGRWfAFqJwdj$Ye$vI&F literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00025.chunk b/nix/leios-mvd/immdb-node/immutable/00025.chunk new file mode 100644 index 0000000000000000000000000000000000000000..7ff8f1eafb7141a17e22c9b1e076e4885c1a7268 GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7%3S7^jIJce{NvBlT$~i7ri&Mls87(<)DyS4~O{oZyH!=gU5JS zAZrs&bL|Y$PiV-X?FjuO-QT>bHbrBvG=QZi_epguxmX~r8<&tu(VcLEq8IWwUWpNj z{sl%sO8Yo_|gHaQ`9~iX05y`jdNnMjk&cI|7Ij!@u$E zo77=};pe0RB5oDR(m?u}T&puug?8UfYv|3iufocnZ>K%u=jxx`-tul9?G~DrXZ$s>}vS+E+`{*SpWgEKfa6eIAc0Xgnofuh?As(g#&D%PpNr@AF>TDnn-|JpV>3rp>%Gjc z%M#4Zk&g}oX^UoSvQH&oBT80$wie#JN7{;@@mLq4i#9+EQUa_(zwm#w_RP%tguv5?X`H?yll+unFQ8Z+4-5IvuyS^j-6>2i2= zoTO^$;#G5S2=J30Kb&8>7*}?krP7qB%|=!C)H&_9p>(jE76}1)l-%94;8p{oiD{LO zDV4>`+(o$AQHY38dF0u>41WmvfbH?j>xCZRH{a{H0(UcS!c?l84MNV}Q_X6R!x9G{ z*z2g>&$7qurToMaR25%yo&fH4JSp4V8Mx8uQ4pDylNX;p51z*!+(uVtX!srx$Nt^# zb>1dcv+*QX5us+b^k*LQRtT&UKC@Q!=wyj*#TcLXKSN z5JHY}jbxjYRWdiZ!uNT;-+$oy!}o{hhwmTpe!b&FXmN=$+Ok4009DaaXqM8JJZ7x_ zt;fQ6n(jGYSRN1miCDN+P0#e+s0C1|oz5XoGBLRNHiiV_4b6d|H3+y;q62^;S=i0~ z$q4`zZA5g8row+l$SFj=e&*E9DAR-NuY?CJO=kxzp0;s|11$6e)VhYyt~uygj&Ajs zK}%PB$Zc0_AB#V}ReS>*2u-cD3>fkEc2UMhJlfy(_B5{^!BWw+E6wyV?+NBPMFDun zu*C*Ae*>X7M%oZNsk#)QW4}H2*p$81`R)TwZ{&4iPZTpgXwynH3UqjdpYVQS4!5Ps zquHm8cr;1d?boiltZ~>!n2UVUVO=0zH3HiMptOjJ$c5OD95Y)V8BdWvW;P5&o6S2B z23Bv*D!aO~7ykrMoP_gh(SHcFpLbVN|3IsAm$QuAG`D0W_!(P3gKNWDK_I~5on~I* zn5{;zbG;-kb(dFk+rD+onZiBj%z_c%5^Yn{c``=Bsh!Cn^5zp(@EfD0uOgoJkr{{2 zdlzndZ&4s|qCzeLEp>r!l3eaM4#yMKe3Fp3m#nm|tu+Oc#F-8ON?wsutftPpj!_l{ z=TI=O8D%UHqn>UR)hyq?rzrZzW)`s;ydb~~QXVqSUPuEcoUsk_BEE0zW6s}jK2d+% zYp6W%m8;rzt7-`~3$L7|tg_zQletejR(!lCiMOwC z)I4IaE-u6WXv183Fm|ndUW)Io8?^_$hsi0(t_{ybZnxsUA2Pkj)iYSRr^dwIT{>d$ zaSoYa7Qno%I*mn-3SOu0pPJbW9WLhQP&`C)K8y6WU7th=U)crS zRH=x5>jpsZu`OXfiXOSqwHIfdemeH+BOkciYtQ4#U{y!a{9bsz^Q5xy%of;=e$Db0 z!ethiNMEI0h4T7Vz(J~3yufW!AL%W?OgJc~+re@rvz~Ku9=jawWJ0CpQ{(;(OGj2n z9zcaFmdN?KtkYA6#g$KO`?5!{X;CFKjh7k==2A`~Nm>6RSQANDyZj(q!d_;s?+0Rl zW~y(wTSnlF6uddhRX}l=D?vWRpJ-;w(s*JV#Lbm0|4G| z<XE5`FH%8Sk=H%mHFWDBSZ3beMcRH{}1b*0!vp`NDDyi zwO*I1OD7au&VB&1LnboRT_qv78cdWLR$TULd3Y3n3Pjk4&cX)I`gP^cLbla76VI83 z))$``P>VIzPKE0>{k5KaW-4yre#ngi=_OrxKZw1lQR)=xo%uG z=dL}Og{i9s@T{aRKSWifX@3$Kp9h6C+`sE##}7z|rGDdyUp*a&?rxoN`?Yds2cbT0 zq0Tk5s>L+rABTU;5L7UqTkk$_$~zI0XCE7PrCO_d7iZEb{@=l3UpJDOB(qnv4%RM! z0G$C=UFwdlX7g&pHGswu^F{tWmc*#n!=nVKaB?zD@67sdQ*DES*Cr2~{SnqqB6f(n zRLPC(q%`T>z!+nt4lML!8zK#FAn5Rz`ePS@wW|wXiT!6R`t{KZH*4%t+BtrLnkRl!mJ6j6uInNM^9h-Jv_H4VEXg9&=AN1 zUCBJx9IGX)e)rkB(0r_mod3P_38XJ1 sbGhP`&F?oKwbHs{bf;By=Gxko7g*VkoRBE`wvyjv?%X0@cBnp00C7<>H2?qr literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00027.chunk b/nix/leios-mvd/immdb-node/immutable/00027.chunk new file mode 100644 index 0000000000000000000000000000000000000000..ec4d2a34d70e66fa7068dda3e1bb587970eea2ff GIT binary patch literal 1714 zcmV;j22J^b2Ze%)7%dqCDp(-Yv+uLTIx5^U+=V5Xt$nG`1qZ~)7;^Th4@8}va!m(V zAZrs&bL|Y$PiV-X?FjuO-QT>bHbrBvG=QZi_epguxmX~r8<&tu(VcLEq8IWwUWpNj z{sl%sbZlJ5BLvYmv)>&y(aS>oAJDp*sK&u&eaCF1etY{IGQ)g+23Es% zW;jbKdcgG$1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmYeHyGi0 z-1I3Wv+w{|E78@pkp4(0yY;tnScTmSXBGeeSU?chVWB%#2?mXgg)L0@J>>}vS+E+`{*SpWgEKfa6eIAu~fNkuTY?9_<|k|@navJtJcs!+jf82R%JpSrY*WYqd|VwlYEsL z_+Nz-k^fl$X^UoSvQH&oBT80$wie#JN7{;@@mLq4i#9+EQUa_(zwm#w_RP%tguv5?X`H?yll+unFQ8Z+4-5IvuyS^j-6>2i2= zoTO^$;#G5S2=J30Kb&8>7*}?krP7qB%|=!C)H&_9p>(jE76}1)l-%94;8p{oiD{LO zDV4>`+(o$AQHY38dF0u>41WmvfbH?j>xCZRH{a{H0(UcS!c?l84MNV}Q_X6R!x9G{ z*z2g>&$7qurToMaR25%yo&fH4JSp4V8Mx8uQ4pDylNX;p51z*!+(uVtX!srx$Nt^# zb>1dcv+*QX5us+b^k*LQRtT&UKC@Q!=w1(pXx2eri~x z84QNd;on#wem7TAet;78b{ZUa!Man#l&LKU6|NF)^68pt@k>Tsf>=Nw`?s#HNpWd$ zR214wuU@R`8VM!Z5^jFZw4w-;pXJ+Q9(kgp(-Gd_p=4+K~sDOVj9@PTlfJV<32Uig|%K9LU;NB@|K+5NPQuw#eBLEg)eKe=5X0o@o)|aOkjISxdHS!_Z^bwA z<_BP%7M3wvVx#?H`+Nw33IkaIz``S-j%Rc~23H_TjI#`&mZi8Z^tCLtx2=3iIZL!i z$u<>A0hb6%a;!-feqWsi{%f)!2bofExEkYV7a7W zr$YBO37g!!s1BrD;!y!0EQv0e#u=}2vC8*bY&f1oPM)o?Njzr&@UFBUQR0SN~sL6J233b5};J! z9|r6D1x=H3LWmPt?O5NH^@VW><<0a3ZX!eFYyCQ97yDQ|25y_mQ9|^Ww%teXHS={- IIe>tmfGZJ8-v9sr literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00027.primary b/nix/leios-mvd/immdb-node/immutable/00027.primary new file mode 100644 index 0000000000000000000000000000000000000000..0cbb4768759ac0e5d582408a1b83f7623396caf1 GIT binary patch literal 129 UcmZQ%KmZFMlUld{Xckcz0Jg~p`Tzg` literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00027.secondary b/nix/leios-mvd/immdb-node/immutable/00027.secondary new file mode 100644 index 0000000000000000000000000000000000000000..850d3070d03e799ca9d703fe3cbb7301d09c3fa3 GIT binary patch literal 112 zcmZQzfC6Ubpr=zr4&3XXov864^UR6YhgNM*xw7t?QyfhLSy?1CFZxZa%lgc9qAA$d?aic&KWgQNBiwtor3ORQ+X4V**Ck#6 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00028.chunk b/nix/leios-mvd/immdb-node/immutable/00028.chunk new file mode 100644 index 0000000000000000000000000000000000000000..e78a08bd61be025fbc6ee6b31c87c34c8bdc5cb1 GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7%v$EUsxbPHBkiw87a|Dk$!6P3dn*}O-AgJX#6I3!&pa*wq;XT zAdtsYaIcp$O18t45R}D*QC2C^SXz93YFMNh42IC*-&i1iH&;@AfD-n08XR}Qx>LlI zsVxW6&WsOGaISSU@_ZxehXUB$y&PzL$%)o^>2!SSPENP7Mni-YRcu_iGnp z^QGL>lpEb%-_WqL!kRyX+t5o#%%-;?a?w{NK(AO(C4O_6=2$=3Y2YyWnHCvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d^JMdW@r5kr*zo%iA5f;ebNiIo{n$S;LX zZ&#O$ofKXV@BylBAJaIR@R0?HOh|NLSI@Z3s_%nTM7BX;)2wU1S|t6#BBp?tP#>5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQYD@&h; literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00028.primary b/nix/leios-mvd/immdb-node/immutable/00028.primary new file mode 100644 index 0000000000000000000000000000000000000000..0ffe1bf2590a2b0271a0fc1879f8aec21f8a7160 GIT binary patch literal 129 QcmZQ%pbxMBT7wk>02Jy0iU0rr literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00028.secondary b/nix/leios-mvd/immdb-node/immutable/00028.secondary new file mode 100644 index 0000000000000000000000000000000000000000..79862e0ca717812d3d67f15050a11d2e1e6b7780 GIT binary patch literal 56 zcmZQzfC6UbptNNjBD{PNwl!k&Yk41^`B%MW|K|wfH_kW8?W7N30$LlI zsVxW6&WsOGaISSU^>Ci=mEWb0Ugc{a2%e!ZFhPm7^+>BOk(#hd|S2F^0QV zw>^sTfa=Ji_*Zb^O^tjG6G!-B*Z-`N+$IuO;N4hIQz4=yzS#z+n$>5ptyfLM#;ME5 zf0316Lr!+e(}g9S9Usk8_cI{h6S;0|-s)4ypH<$>aY}8u@R;NDjP1HC0ym92GP!O7 z5!D5mjKpIP1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmbrTlao@ z1H@ZiBqrE}wO$%Rcltj<)rn|0KnZWNbix1tSU}Dwo{HH>CvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0dh zw7jtRc55;Q@BylBAJaIR@R0?HOh|NLSI@Z3s_%nTM7BX;)2wU1S|t6#BBp?tP#>5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQY77V66 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00029.primary b/nix/leios-mvd/immdb-node/immutable/00029.primary new file mode 100644 index 0000000000000000000000000000000000000000..30f45b3e3e748ab99eea218c3fd08b8acb9ff84b GIT binary patch literal 129 QcmZQ%pf0cg8b=Za07x1F+5i9m literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00029.secondary b/nix/leios-mvd/immdb-node/immutable/00029.secondary new file mode 100644 index 0000000000000000000000000000000000000000..8b674ff078177d4b47990dc5abdbcbd904a30e65 GIT binary patch literal 56 zcmZQzfC6Ubp!E!=9t(U5o%XhPrGl)!_G}T)W3%*F<}$w&uFOq3yr?*T)#przYUXkP D#mW(P literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00030.chunk b/nix/leios-mvd/immdb-node/immutable/00030.chunk new file mode 100644 index 0000000000000000000000000000000000000000..0ccfdda5c10c8d2aae5967a9c4cd04f7d87ef8a7 GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7%>?Gi&!8K@>Q1YbEzO5FDsiANyeHk1f2uv6M1c7!=iILlI zsVxW6&WsOGaISSU|&x_+(W|&$xDpxwNz50^)I8M4-l3R6Kdt;KRz3kZATj zj92;@l(L&7xjmvuf&_fK0?Cp=5+R1er#0+H?(|qt+>>wo-|DS(3xms7lE1iC&u;El zJd8MYv<*3CvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0dU>zqHrO0+VIAC>Ja~Gve`WPv#E;^ANA*x*)VbX|Ssy4tqMj z=Vg>G5+El9@BylBAJaIR@R0?HOh|NLSI@Z3s_%nTM7BX;)2wU1S|t6#BBp?tP#>5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQY!}y|h literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00030.primary b/nix/leios-mvd/immdb-node/immutable/00030.primary new file mode 100644 index 0000000000000000000000000000000000000000..6e677301ffd491e8c4769d7f2d04f7e490c72301 GIT binary patch literal 129 QcmZQ%AP!gnmC*zP0OM)}3IG5A literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00030.secondary b/nix/leios-mvd/immdb-node/immutable/00030.secondary new file mode 100644 index 0000000000000000000000000000000000000000..d1f503848463552ecd047e662f890653f09ca8dd GIT binary patch literal 56 zcmZQzfC6UbpvgxHX5Q)ES@2<1%ne2B4S%_sqkmPf#_p!Ejx#7& zAZrs&bL|Y$PiV-X?FjuO-QT>bHbrBvG=QZi_epguxmX~r8<&tu(VcLEq8IWwUWpNj z{sl%s{5ln||&7N zXr!hH&OFwX&~Dl;8AUm9-i_#=d#`77X~#Fd)MWjqRZ%EZv4$%@2)x|t-ML(DZ968# zK9^>QU>RWv1Xv&`R~;7cfpD8VNM#sc2Yc)JGzz;v#}hO|#ZMnvUfl77SRmYeHyGi0 z-1I3Wv+w{|E78@pkp4(0yY;tnScTmSXBGeeSU?chVWB%#2?mXgg)L0@J>>}vS+E+`{*SpWgEKfa6eIA z=hJ%Q!!%d@_YPnD+*UhPbI3z@MW}B8ReUEd+%o&E(?UsSXySg zP=n|KEPdPxX^UoSvQH&oBT80$wie#JN7{;@@mLq4i#9+EQUa_(zwm#w_RP%tguv5?X`H?yll+unFQ8Z+4-5IvuyS^j-6>2i2= zoTO^$;#G5S2=J30Kb&8>7*}?krP7qB%|=!C)H&_9p>(jE76}1)l-%94;8p{oiD{LO zDV4>`+(o$AQHY38dF0u>41WmvfbH?j>xCZRH{a{H0(UcS!c?l84MNV}Q_X6R!x9G{ z*z2g>&$7qurToMaR25%yo&fH4JSp4V8Mx8uQ4pDylNX;p51z*!+(uVtX!srx$Nt^# zb>1dcv+*QX5us+b^k*LQRtT&UKC@Q!=w^-u1Lidl(n}UIz$?WGoKYOyRO=t27yBH>jYUUdN D>dX^4 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00033.chunk b/nix/leios-mvd/immdb-node/immutable/00033.chunk new file mode 100644 index 0000000000000000000000000000000000000000..2f88e7d0055066d0b657ba0b9a7787c8ded7f991 GIT binary patch literal 857 zcmV-f1E&0f2Ze%)7&93I;#eSRM@lueLlnKlvyhAUiP;fRiDL)O^XBBXhAfk)K3oD= zAdtsYaIcp$O18t45R}D*QC2C^SXz93YFMNh42IC*-&i1iH&;@AfD-n08XR}Qx>LlI zsVxW6&WsOGaISSU?-t-noy4fN_c^PK_V1a5;-;k*TwJ`ZOEgQ>qRQhX z{jWF4C}ycp^8796B1aRoLB{E=-^!b&*i*FB9{dTGcSB!7!4UO6GiHn835X9Tq0b$K z-h*UCvQ}?5lWE%<)n;G!r4@O z-X&Dk3|0~l!{q6n7&p|A$Bh7a`mfb*#W(Wi2Vk8RmN8pmqy1w0d5d zA^6P8mk%m|4cp6$u#)TQj3pggKD$(8x(chF(N;z;o;99`UM_-?=4?50p{y~;IYRO#O*a2xFO#5G8% z1+=8zl;jBB#M@D0Tj1;{Ii>t8^&Gm|mQr8QSDMU^39T^J`Z_~id@!;uW^)?B2w}M* z3pz!2b8jy*r>U(_HTRXy`)t|7vV30(o8kw|!+qf(25tWUh9Rwf$z50oP=Ua7WgTCf zezRlkQ}$BOFBYF(PAcz8sSL0?Fzn0{pj6=>2J8C;O_Op$h!a`uSl^ZPg>ebx&GZFs jB17eC{W@hA`&c{%Zkx(cLiCrm-AC^=^L0}>fPkQY)sCpl literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00033.primary b/nix/leios-mvd/immdb-node/immutable/00033.primary new file mode 100644 index 0000000000000000000000000000000000000000..4c8c64f175515226b61e934848a77a5121befa91 GIT binary patch literal 29 LcmZQ%zzr+_0CE62 literal 0 HcmV?d00001 diff --git a/nix/leios-mvd/immdb-node/immutable/00033.secondary b/nix/leios-mvd/immdb-node/immutable/00033.secondary new file mode 100644 index 0000000000000000000000000000000000000000..ac158489b4e070f434ba5b1c156b5a2936a5776b GIT binary patch literal 56 zcmZQzfC6Ubp#5(HZPQx6_!~Lfa)@tx`}OAou2qYV%t%$)u_bt!LQ}Z=O0zQ%)y$6o D_WToc literal 0 HcmV?d00001 From ba949db887974457bee44afe047b86f0235e9984 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 13:46:38 +0200 Subject: [PATCH 022/119] Configure the private testnet such that it doesn't update the system start time --- flake.lock | 11 ++++++----- flake.nix | 2 +- nix/leios-mvd/immdb-node/service.nix | 1 + nix/leios-mvd/leios-node/os.nix | 2 ++ 4 files changed, 10 insertions(+), 6 deletions(-) diff --git a/flake.lock b/flake.lock index 27aca49dcf..9128a4e184 100644 --- a/flake.lock +++ b/flake.lock @@ -454,15 +454,16 @@ "treefmt-nix": "treefmt-nix" }, "locked": { - "lastModified": 1758296791, - "narHash": "sha256-n24MZIYh1iVV2BTYEcC9nKzvMpjl7JTK1LAxU1caMOM=", - "owner": "mlabs-haskell", + "lastModified": 1760526797, + "narHash": "sha256-xODMhuzz5aVJE68CJwZiLpXa0zihgT2PAhJBowt9gjw=", + "owner": "bladyjoker", "repo": "cardano.nix", - "rev": "658bbc86da1f2dc61faa0316b148d71228975860", + "rev": "8b0f4ec95ae1d4ee36c7f47b10ce78211de79031", "type": "github" }, "original": { - "owner": "mlabs-haskell", + "owner": "bladyjoker", + "ref": "bladyjoker/add-update-system-start-time-option", "repo": "cardano.nix", "type": "github" } diff --git a/flake.nix b/flake.nix index 79ba2958b9..778aafea89 100644 --- a/flake.nix +++ b/flake.nix @@ -41,7 +41,7 @@ url = "github:phadej/gentle-introduction"; flake = false; }; - cardano-nix.url = "github:mlabs-haskell/cardano.nix"; + cardano-nix.url = "github:bladyjoker/cardano.nix?ref=bladyjoker/add-update-system-start-time-option"; }; outputs = inputs: let diff --git a/nix/leios-mvd/immdb-node/service.nix b/nix/leios-mvd/immdb-node/service.nix index 27d80f1ce0..825a9411ad 100644 --- a/nix/leios-mvd/immdb-node/service.nix +++ b/nix/leios-mvd/immdb-node/service.nix @@ -142,6 +142,7 @@ in mkdir $STATE_DIRECTORY/immutable; cp -r ${cfg.db}/* $STATE_DIRECTORY/immutable; + chmod +rw $STATE_DIRECTORY/immutable/*; immdb-server \ --db $STATE_DIRECTORY/immutable \ diff --git a/nix/leios-mvd/leios-node/os.nix b/nix/leios-mvd/leios-node/os.nix index c71b57c8a5..821fc728a2 100644 --- a/nix/leios-mvd/leios-node/os.nix +++ b/nix/leios-mvd/leios-node/os.nix @@ -20,6 +20,8 @@ operationalCertificate = ./opcert; delegationCertificate = ./delegation-cert.json; signingKey = ./delegate.key; + + updateSystemStartTime = false; }; }; } From 2cb6afadcfb46cf74bae9a08083998a72e7a862f Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 15 Oct 2025 17:12:33 +0200 Subject: [PATCH 023/119] Add README.md for Leios MVD and an actual test scenario condition --- flake.lock | 6 ++--- nix/leios-mvd/README.md | 50 +++++++++++++++++++++++++++++++++++++++++ nix/leios-mvd/test.nix | 10 +++++++++ 3 files changed, 63 insertions(+), 3 deletions(-) create mode 100644 nix/leios-mvd/README.md diff --git a/flake.lock b/flake.lock index 9128a4e184..aa11e14711 100644 --- a/flake.lock +++ b/flake.lock @@ -454,11 +454,11 @@ "treefmt-nix": "treefmt-nix" }, "locked": { - "lastModified": 1760526797, - "narHash": "sha256-xODMhuzz5aVJE68CJwZiLpXa0zihgT2PAhJBowt9gjw=", + "lastModified": 1760535825, + "narHash": "sha256-odWQSUOkj1j20sml+yIEeQ3gWs35hN+XExPmpyCWnc8=", "owner": "bladyjoker", "repo": "cardano.nix", - "rev": "8b0f4ec95ae1d4ee36c7f47b10ce78211de79031", + "rev": "8e80c0630e6c5a17976c59a1b63f900a283243ab", "type": "github" }, "original": { diff --git a/nix/leios-mvd/README.md b/nix/leios-mvd/README.md new file mode 100644 index 0000000000..d54a1a553c --- /dev/null +++ b/nix/leios-mvd/README.md @@ -0,0 +1,50 @@ +# Leios MVD + +Leios Minimum Viable Demo branch with NixOS test based setup for spawning reproducible and/or interactive demo scenarios. + +## Files and directories + +- `./test.nix` contains the NixOS test definition where we can script various scenarios. +- `./leios-node/` contains the NixOS definition for the "leios-node" that runs the "Ouroboros Leios" patched cardano-node under test. +- `./immdb-node/` contains the NixOS definition for the "immdb-node" that runs the Immutable DB server. + +## Running the test + +To run the test scenario with Nix: + +```shell +$ nix build .#leios-mvd-test +``` + +Once it finishes the `result` directory will contains the logs collected from the "leios-node": + +```shell +$ ls result +cardano-node.logs + +$ tail result/cardano-node.logs +Oct 15 14:58:07 leios-node cardano-node-start[741]: {"at":"2025-10-15T14:58:07.199318758Z","ns":"Net.ConnectionManager.Local.ConnectionManagerCounters","data":{"kind":"ConnectionManagerCounters","state":{"duplex":0,"fullDuplex":0,"inbound":1,"outbound":0,"unidirectional":1}},"sev":"Debug","thread":"42","host":"leios-node"} +... +``` + +## Interactive demo + +Fun part! To start the nodes defined by the test scenario run: + +```shell +$ nix run .#leios-mvd-test.driverInteractive +additionally exposed symbols: + immdb-node, leios-node, + vlan1, + start_all, test_script, machines, vlans, driver, log, os, create_machine, subtest, run_tests, join_all, retry, serial_stdout_off, serial_stdout_on, polling_condition, Machine +>>> +``` + +This puts you in a IPython shell. To start all nodes run: + +```python +>>> start_all() +``` + +After a bit you should see QEMU windows corresponding to each node in the test scenario. +Login as "root". diff --git a/nix/leios-mvd/test.nix b/nix/leios-mvd/test.nix index 31af30ed9c..169cd6a570 100644 --- a/nix/leios-mvd/test.nix +++ b/nix/leios-mvd/test.nix @@ -24,7 +24,17 @@ testScript = '' start_all() + # Wait until the respective services are up immdb_node.wait_for_unit("immdb-server.service") leios_node.wait_for_unit("cardano-node.service") + + # Wait until leios-node synced with immdb-node + # NOTE(bladyjoker): Block 51 is the tip + # [0.139717s] BlockNo 51 SlotNo 994 6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc + leios_node.wait_until_succeeds("cardano-cli query tip | grep hash | grep -q '6685f4'") + + # Collect logs from leios-node (read them in result/cardano.logs) + leios_node.execute("journalctl -u cardano-node --no-pager > cardano-node.logs") + leios_node.copy_from_vm("cardano-node.logs", "") ''; } From d2ab9f111b15c3b1713e4f684198fccaf735d00f Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 15 Oct 2025 08:57:37 -0700 Subject: [PATCH 024/119] leiosdemo202510: merge ebBodies and ebClosures, use only points in CLI, improve column names --- ouroboros-consensus/app/leiosdemo202510.hs | 227 ++++++++++----------- 1 file changed, 107 insertions(+), 120 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 6bd1cbbe09..8f1b957600 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -49,13 +49,12 @@ main = getArgs >>= \case db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen generateDb prng0 db manifest - ["MsgLeiosBlockRequest", dbPath, ebSlotStr, ebHashStr] + ["MsgLeiosBlockRequest", dbPath, ebPointStr] | ".db" `isSuffixOf` dbPath - , Just ebSlot <- readMaybe ebSlotStr - , Right ebHash <- BS16.decode (fromString ebHashStr :: ByteString) + , Just ebPoint <- readMaybe ebPointStr -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockRequest db ebSlot ebHash + msgLeiosBlockRequest db ebPoint ["MsgLeiosBlock", dbPath, ebPointStr, ebSlotStr, ebPath] | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebPath @@ -64,14 +63,13 @@ main = getArgs >>= \case -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlock db ebPoint ebSlot ebPath - "MsgLeiosBlockTxsRequest" : dbPath : ebSlotStr : ebHashStr : bitmapChunkStrs + "MsgLeiosBlockTxsRequest" : dbPath : ebPointStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath - , Just ebSlot <- readMaybe ebSlotStr - , Right ebHash <- BS16.decode (fromString ebHashStr :: ByteString) + , Just ebPoint <- readMaybe ebPointStr , Just bitmaps <- parseBitmaps bitmapChunkStrs -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps + msgLeiosBlockTxsRequest db ebPoint bitmaps "MsgLeiosBlockTxs" : dbPath : ebPointStr : ebTxsPath : bitmapChunkStrs | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebTxsPath @@ -81,9 +79,9 @@ main = getArgs >>= \case db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ - \ OR $0 MsgLeiosBlockRequest myDatabase.db ebSlot ebHash(hex)\n\ - \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) ebSlot myEb.bin\n\ - \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlockRequest myDatabase.db ebPoint(int)\n\ + \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) myEb.bin\n\ + \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebPoint(int) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ \ OR $0 MsgLeiosBlockTxs myDatabase.db ebPoint(int) myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ \" @@ -119,9 +117,8 @@ generateDb prng0 db ebRecipes = do gref <- R.newIOGenM prng0 -- init db withDieMsg $ DB.exec db (fromString sql_schema) - stmt_insert_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoints) - stmt_insert_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBodies) - stmt_insert_ebClosures <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosures) + stmt_write_ebPoint <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoint) + stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) forM_ ([(0 :: Word16) ..] `zip` ebRecipes) $ \(ebPoint, ebRecipe) -> do -- generate txs, so we have their hashes @@ -137,9 +134,10 @@ generateDb prng0 db ebRecipes = do | txByteSize < (maxBound :: Word16) = 3 | txByteSize < fromIntegral (maxBound :: Word32) = 5 | otherwise = 9 - txBytes <- R.uniformByteStringM (fromIntegral txByteSize - overhead) gref - let txCborBytes = serialize' $ CBOR.encodeBytes txBytes - pure (txCborBytes, Hash.hashWith id txCborBytes :: Hash.Hash HASH ByteString) + txBytes <- id + $ fmap (serialize' . CBOR.encodeBytes) + $ R.uniformByteStringM (fromIntegral txByteSize - overhead) gref + pure (txBytes, Hash.hashWith id txBytes :: Hash.Hash HASH ByteString) let ebSlot = slotNo ebRecipe let ebHash :: Hash.Hash HASH ByteString ebHash = @@ -148,27 +146,22 @@ generateDb prng0 db ebRecipes = do (encodeEB (fromIntegral . BS.length) Hash.hashToBytes) txs withDieMsg $ DB.exec db (fromString "BEGIN") - withDie $ DB.bindInt64 stmt_insert_ebPoints 3 (fromIntegral ebPoint) - withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) - withDie $ DB.bindInt64 stmt_insert_ebClosures 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_write_ebPoint 3 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegral ebPoint) -- INSERT INTO ebPoints - withDie $ DB.bindInt64 stmt_insert_ebPoints 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_insert_ebPoints 2 (Hash.hashToBytes ebHash) - withDieDone $ DB.stepNoCB stmt_insert_ebPoints - withDie $ DB.reset stmt_insert_ebPoints + withDie $ DB.bindInt64 stmt_write_ebPoint 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_write_ebPoint 2 (Hash.hashToBytes ebHash) + withDieDone $ DB.stepNoCB stmt_write_ebPoint + withDie $ DB.reset stmt_write_ebPoint -- loop over txs - V.iforM_ txs $ \txOffset (txCborBytes, txHash) -> do - withDie $ DB.bindInt64 stmt_insert_ebBodies 2 (fromIntegral txOffset) - withDie $ DB.bindInt64 stmt_insert_ebClosures 2 (fromIntegral txOffset) - -- INSERT INTO ebBodies - withDie $ DB.bindBlob stmt_insert_ebBodies 3 (Hash.hashToBytes txHash) - withDie $ DB.bindInt64 stmt_insert_ebBodies 4 (fromIntegral (BS.length txCborBytes)) - withDieDone $ DB.stepNoCB stmt_insert_ebBodies - withDie $ DB.reset stmt_insert_ebBodies - -- INSERT INTO ebClosures - withDie $ DB.bindBlob stmt_insert_ebClosures 3 txCborBytes - withDieDone $ DB.stepNoCB stmt_insert_ebClosures - withDie $ DB.reset stmt_insert_ebClosures + V.iforM_ txs $ \txOffset (txBytes, txHash) -> do + -- INSERT INTO ebTxs + withDie $ DB.bindInt64 stmt_write_ebClosure 2 (fromIntegral txOffset) + withDie $ DB.bindBlob stmt_write_ebClosure 3 (Hash.hashToBytes txHash) + withDie $ DB.bindInt64 stmt_write_ebClosure 4 (fromIntegral (BS.length txBytes)) + withDie $ DB.bindBlob stmt_write_ebClosure 5 txBytes + withDieDone $ DB.stepNoCB stmt_write_ebClosure + withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") -- finalize db @@ -179,9 +172,9 @@ generateDb prng0 db ebRecipes = do sql_schema :: String sql_schema = "CREATE TABLE txCache (\n\ - \ txHash BLOB NOT NULL PRIMARY KEY -- raw bytes\n\ + \ txHashBytes BLOB NOT NULL PRIMARY KEY -- raw bytes\n\ \ ,\n\ - \ txCborBytes BLOB NOT NULL -- in CBOR\n\ + \ txBytes BLOB NOT NULL -- valid CBOR\n\ \ ,\n\ \ expiryUnixEpoch INTEGER NOT NULL\n\ \ ) WITHOUT ROWID;\n\ @@ -191,31 +184,21 @@ sql_schema = \ ,\n\ \ ebHash BLOB NOT NULL\n\ \ ,\n\ - \ id INTEGER NOT NULL UNIQUE\n\ + \ id INTEGER NOT NULL\n\ \ ,\n\ \ PRIMARY KEY (ebSlot, ebHash)\n\ \ ) WITHOUT ROWID;\n\ \\n\ - \CREATE TABLE ebBodies (\n\ + \CREATE TABLE ebTxs (\n\ \ ebPoint INTEGER NOT NULL -- foreign key ebPoints.id\n\ \ ,\n\ \ txOffset INTEGER NOT NULL\n\ \ ,\n\ - \ txHash BLOB NOT NULL -- raw bytes\n\ + \ txHashBytes BLOB NOT NULL -- raw bytes\n\ \ ,\n\ - \ txSizeInBytes INTEGER NOT NULL\n\ + \ txByteSize INTEGER NOT NULL\n\ \ ,\n\ - \ missing BOOLEAN NOT NULL\n\ - \ ,\n\ - \ PRIMARY KEY (ebPoint, txOffset)\n\ - \ ) WITHOUT ROWID;\n\ - \\n\ - \CREATE TABLE ebClosures (\n\ - \ ebPoint INTEGER NOT NULL -- foreign key ebPoints.id\n\ - \ ,\n\ - \ txOffset INTEGER NOT NULL\n\ - \ ,\n\ - \ txCborBytes BLOB NOT NULL -- in CBOR\n\ + \ txBytes BLOB -- valid CBOR\n\ \ ,\n\ \ PRIMARY KEY (ebPoint, txOffset)\n\ \ ) WITHOUT ROWID;\n\ @@ -223,33 +206,29 @@ sql_schema = sql_index_schema :: String sql_index_schema = - "-- Helps with the eviction policy of the EbStore.\n\ - \CREATE INDEX ebPointsExpiry\n\ - \ ON ebPoints (ebSlot, id);\n\ + "CREATE INDEX ebPointsExpiry\n\ + \ ON ebPoints (ebSlot, id); -- Helps with the eviction policy of the EbStore.\n\ \\n\ - \-- Helps with the eviction policy of the TxCache.\n\ \CREATE INDEX txCacheExpiry\n\ - \ ON txCache (expiryUnixEpoch, txHash);\n\ + \ ON txCache (expiryUnixEpoch, txHashBytes); -- Helps with the eviction policy of the TxCache.\n\ \\n\ - \-- Helps with the eviction policy of the fetch logic's todo list.\n\ \CREATE INDEX missingEbTxs\n\ - \ ON ebBodies (ebPoint, txOffset)\n\ - \ WHERE missing = TRUE;\n\ + \ ON ebTxs (ebPoint, txOffset)\n\ + \ WHERE txBytes IS NULL; -- Helps with fetch logic decisions.\n\ + \\n\ + \CREATE INDEX acquiredEbTxs\n\ + \ ON ebTxs (ebPoint, txOffset)\n\ + \ WHERE txBytes IS NOT NULL; -- Helps with fetch logic decisions.\n\ \" -sql_insert_ebPoints :: String -sql_insert_ebPoints = +sql_insert_ebPoint :: String +sql_insert_ebPoint = "INSERT INTO ebPoints (ebSlot, ebHash, id) VALUES (?, ?, ?)\n\ \" -sql_insert_ebBodies :: String -sql_insert_ebBodies = - "INSERT INTO ebBodies (ebPoint, txOffset, txHash, txSizeInBytes, missing) VALUES (?, ?, ?, ?, FALSE)\n\ - \" - -sql_insert_ebClosures :: String -sql_insert_ebClosures = - "INSERT INTO ebClosures (ebPoint, txOffset, txCborBytes) VALUES (?, ?, ?)\n\ +sql_insert_ebClosure :: String +sql_insert_ebClosure = + "INSERT INTO ebTxs (ebPoint, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ \" ----- @@ -281,9 +260,9 @@ withDieJust io = ----- encodeEbPair :: (b -> Word16) -> (h -> ByteString) -> (b, h) -> CBOR.Encoding -encodeEbPair bytesToLen hashToBytes (txCborBytes, txHash) = +encodeEbPair bytesToLen hashToBytes (txBytes, txHash) = CBOR.encodeBytes (hashToBytes txHash) - <> CBOR.encodeWord16 (bytesToLen txCborBytes) + <> CBOR.encodeWord16 (bytesToLen txBytes) encodeEB :: Foldable f => (b -> Word16) -> (h -> ByteString) -> f (b, h) -> CBOR.Encoding encodeEB bytesToLen hashToBytes ebPairs = @@ -324,20 +303,19 @@ pushX (X n xs vs) x = if n < 1024 then X (n+1) (x : xs) vs else X 1 [x] (V.fromList xs : vs) -msgLeiosBlockRequest :: DB.Database -> Word64 -> ByteString -> IO () -msgLeiosBlockRequest db ebSlot ebHash = do +msgLeiosBlockRequest :: DB.Database -> Int -> IO () +msgLeiosBlockRequest db ebPoint = do -- get the EB items stmt_lookup_ebBodies <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) - withDie $ DB.bindInt64 stmt_lookup_ebBodies 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_lookup_ebBodies 2 ebHash + withDie $ DB.bindInt64 stmt_lookup_ebBodies 1 (fromIntegral ebPoint) let loop !acc = do withDie (DB.stepNoCB stmt_lookup_ebBodies) >>= \case DB.Done -> pure acc DB.Row -> do -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? - txHash <- DB.columnBlob stmt_lookup_ebBodies 0 - txSizeInBytes <- DB.columnInt64 stmt_lookup_ebBodies 1 - loop $ pushX acc (txSizeInBytes, txHash) + txHashBytes <- DB.columnBlob stmt_lookup_ebBodies 0 + txByteSize <- DB.columnInt64 stmt_lookup_ebBodies 1 + loop $ pushX acc (txByteSize, txHashBytes) acc <- loop emptyX -- combine the EB items BS.putStr @@ -350,14 +328,13 @@ msgLeiosBlockRequest db ebSlot ebHash = do -- logic naturally reverses it sql_lookup_ebBodies_DESC :: String sql_lookup_ebBodies_DESC = - "SELECT ebBodies.txHash, ebBodies.txSizeInBytes FROM ebBodies\n\ - \INNER JOIN ebPoints ON ebBodies.ebPoint = ebPoints.id\n\ - \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ?\n\ - \ORDER BY ebBodies.txOffset DESC\n\ + "SELECT txHashBytes, txByteSize FROM ebTxs\n\ + \WHERE ebPoint = ?\n\ + \ORDER BY txOffset DESC\n\ \" -msgLeiosBlockTxsRequest :: DB.Database -> Word64 -> ByteString -> [(Word16, Word64)] -> IO () -msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do +msgLeiosBlockTxsRequest :: DB.Database -> Int -> [(Word16, Word64)] -> IO () +msgLeiosBlockTxsRequest db ebPoint bitmaps = do do let idxs = map fst bitmaps let maxEbByteSize = 12500000 :: Int @@ -381,8 +358,7 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do -- -- TODO Better workaround for requests of many txs? stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (maxBatchSize `min` numOffsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_lookup_ebClosuresMAIN 2 ebHash + withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebPoint) withDieMsg $ DB.exec db (fromString "BEGIN") acc <- (\f -> foldM f emptyX (batches offsets)) $ \acc batch -> do stmt <- @@ -390,10 +366,9 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do -- this can only be reached for the last batch withDie $ DB.finalize stmt_lookup_ebClosuresMAIN stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (numOffsets `mod` maxBatchSize) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_lookup_ebClosuresTIDY 2 ebHash + withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebPoint) pure stmt_lookup_ebClosuresTIDY - forM_ ([(3 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do + forM_ ([(2 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do withDie $ DB.bindInt64 stmt i (fromIntegral offset) acc' <- (\f -> foldM f acc batch) $ \acc' offset -> do withDie (DB.stepNoCB stmt) >>= \case @@ -401,9 +376,9 @@ msgLeiosBlockTxsRequest db ebSlot ebHash bitmaps = do DB.Row -> do -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? txOffset <- DB.columnInt64 stmt 0 - txCborBytes <- DB.columnBlob stmt 1 + txBytes <- DB.columnBlob stmt 1 when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset - pure $ pushX acc' txCborBytes + pure $ pushX acc' txBytes withDie $ DB.reset stmt pure acc' withDieMsg $ DB.exec db (fromString "COMMIT") @@ -468,32 +443,32 @@ batches xs = if null xs then [] else take maxBatchSize xs : batches (drop maxBat -- 'msgLeiosBlockTxsRequest' logic naturally reverses it sql_lookup_ebClosures_DESC :: Int -> String sql_lookup_ebClosures_DESC n = - "SELECT ebClosures.txOffset, ebClosures.txCborBytes FROM ebClosures\n\ - \INNER JOIN ebPoints ON ebClosures.ebPoint = ebPoints.id\n\ - \WHERE ebPoints.ebSlot = ? AND ebPoints.ebHash = ? AND ebClosures.txOffset IN (" ++ hooks ++ ")\n\ - \ORDER BY ebClosures.txOffset DESC\n\ + "SELECT txOffset, txBytes FROM ebTxs\n\ + \WHERE ebPoint = ? AND txBytes IS NOT NULL AND txOffset IN (" ++ hooks ++ ")\n\ + \ORDER BY txOffset DESC\n\ \" where hooks = intercalate ", " (replicate n "?") ----- +-- | PREREQ: No row in ebTxs already has this ebPoint. msgLeiosBlock :: DB.Database -> Int -> Word64 -> FilePath -> IO () msgLeiosBlock db ebPoint ebSlot ebPath = do ebBytes <- BS.readFile ebPath let ebHash :: Hash.Hash HASH ByteString ebHash = Hash.castHash $ Hash.hashWith id ebBytes - stmt_insert_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoints) - stmt_insert_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBodies) + stmt_write_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoint) + stmt_write_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) withDieMsg $ DB.exec db (fromString "BEGIN") -- INSERT INTO ebPoints - withDie $ DB.bindInt64 stmt_insert_ebPoints 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_insert_ebPoints 2 (Hash.hashToBytes ebHash) - withDie $ DB.bindInt64 stmt_insert_ebPoints 3 (fromIntegral ebPoint) - withDieDone $ DB.stepNoCB stmt_insert_ebPoints - withDie $ DB.reset stmt_insert_ebPoints - -- decode incrementally and simultaneously INSERT INTO ebBodies - withDie $ DB.bindInt64 stmt_insert_ebBodies 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_write_ebPoints 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_write_ebPoints 2 (Hash.hashToBytes ebHash) + withDie $ DB.bindInt64 stmt_write_ebPoints 3 (fromIntegral ebPoint) + withDieDone $ DB.stepNoCB stmt_write_ebPoints + withDie $ DB.reset stmt_write_ebPoints + -- decode incrementally and simultaneously INSERT INTO ebTxs + withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegral ebPoint) let decodeBreakOrEbPair = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> decodeEbPair @@ -501,12 +476,12 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrEbPair bytes go2 txOffset bytes' next go2 txOffset bytes = \case - Just (txHashBytes, txSizeInBytes) -> do - withDie $ DB.bindInt64 stmt_insert_ebBodies 2 txOffset - withDie $ DB.bindBlob stmt_insert_ebBodies 3 txHashBytes - withDie $ DB.bindInt64 stmt_insert_ebBodies 4 (fromIntegral txSizeInBytes) - withDieDone $ DB.stepNoCB stmt_insert_ebBodies - withDie $ DB.reset stmt_insert_ebBodies + Just (txHashBytes, txByteSize) -> do + withDie $ DB.bindInt64 stmt_write_ebBodies 2 txOffset + withDie $ DB.bindBlob stmt_write_ebBodies 3 txHashBytes + withDie $ DB.bindInt64 stmt_write_ebBodies 4 (fromIntegral txByteSize) + withDieDone $ DB.stepNoCB stmt_write_ebBodies + withDie $ DB.reset stmt_write_ebBodies go1 (txOffset + 1) bytes Nothing | not (BSL.null bytes) -> die "Incomplete EB decode" @@ -516,15 +491,20 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") +sql_insert_ebBody :: String +sql_insert_ebBody = + "INSERT INTO ebTxs (ebPoint, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ + \" + msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do ebTxsBytes <- BSL.readFile ebTxsPath - stmt_insert_ebClosures <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosures) - withDie $ DB.bindInt64 stmt_insert_ebClosures 1 (fromIntegral ebPoint) + stmt_write_ebTx <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) + withDie $ DB.bindInt64 stmt_write_ebTx 2 (fromIntegral ebPoint) withDieMsg $ DB.exec db (fromString "BEGIN") - -- decode incrementally and simultaneously INSERT INTO ebClosures + -- decode incrementally and simultaneously UPDATE ebTxs -- - -- TODO also add to TxCache + -- TODO also INSERT INTO TxCache let decodeBreakOrTx = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> CBOR.decodeBytes @@ -535,10 +515,10 @@ msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do Just txBytes -> case offsets of [] -> die "Too many txs" txOffset:offsets' -> do - withDie $ DB.bindInt64 stmt_insert_ebClosures 2 $ fromIntegral txOffset - withDie $ DB.bindBlob stmt_insert_ebClosures 3 $ serialize' $ CBOR.encodeBytes txBytes - withDieDone $ DB.stepNoCB stmt_insert_ebClosures - withDie $ DB.reset stmt_insert_ebClosures + withDie $ DB.bindInt64 stmt_write_ebTx 3 $ fromIntegral txOffset + withDie $ DB.bindBlob stmt_write_ebTx 1 $ serialize' $ CBOR.encodeBytes txBytes + withDieDone $ DB.stepNoCB stmt_write_ebTx + withDie $ DB.reset stmt_write_ebTx go1 offsets' bytes Nothing | not (BSL.null bytes) -> die "Incomplete EB txs decode" @@ -555,3 +535,10 @@ msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do go1 offsets ebTxsBytes2 -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") + +sql_insert_ebTx :: String +sql_insert_ebTx = + "UPDATE ebTxs\n\ + \SET txBytes = ?\n\ + \WHERE ebPoint = ? AND txOffset = ? AND txBytes IS NULL\n\ + \" From 9e3d4273231771e60dbc9e7be64cf4503ab13b03 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 15 Oct 2025 10:26:53 -0700 Subject: [PATCH 025/119] leiosdemo202510: minor refactor --- ouroboros-consensus/app/leiosdemo202510.hs | 37 +++++++++++++--------- 1 file changed, 22 insertions(+), 15 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 8f1b957600..955565e1f4 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -306,15 +306,15 @@ pushX (X n xs vs) x = msgLeiosBlockRequest :: DB.Database -> Int -> IO () msgLeiosBlockRequest db ebPoint = do -- get the EB items - stmt_lookup_ebBodies <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) - withDie $ DB.bindInt64 stmt_lookup_ebBodies 1 (fromIntegral ebPoint) - let loop !acc = do - withDie (DB.stepNoCB stmt_lookup_ebBodies) >>= \case + stmt <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) + withDie $ DB.bindInt64 stmt 1 (fromIntegral ebPoint) + let loop !acc = + withDie (DB.stepNoCB stmt) >>= \case DB.Done -> pure acc DB.Row -> do -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? - txHashBytes <- DB.columnBlob stmt_lookup_ebBodies 0 - txByteSize <- DB.columnInt64 stmt_lookup_ebBodies 1 + txHashBytes <- DB.columnBlob stmt 0 + txByteSize <- DB.columnInt64 stmt 1 loop $ pushX acc (txByteSize, txHashBytes) acc <- loop emptyX -- combine the EB items @@ -337,9 +337,7 @@ msgLeiosBlockTxsRequest :: DB.Database -> Int -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebPoint bitmaps = do do let idxs = map fst bitmaps - let maxEbByteSize = 12500000 :: Int - minTxByteSize = 55 - idxLimit = (maxEbByteSize `div` minTxByteSize) `div` 64 + let idxLimit = maxEbItems `div` 64 when (any (== 0) $ map snd bitmaps) $ do die "A bitmap is zero" when (flip any idxs (> fromIntegral idxLimit)) $ do @@ -389,6 +387,15 @@ msgLeiosBlockTxsRequest db ebPoint bitmaps = do $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak acc putStrLn "" +maxEbBodyByteSize :: Int +maxEbBodyByteSize = 500000 + +minEbItemByteSize :: Int +minEbItemByteSize = (1 + 32 + 1) + (1 + 1) + +maxEbItems :: Int +maxEbItems = (negate 1 + maxEbBodyByteSize - 1) `div` minEbItemByteSize + {- | For example @ print $ unfoldr popLeftmostOffset 0 @@ -499,8 +506,8 @@ sql_insert_ebBody = msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do ebTxsBytes <- BSL.readFile ebTxsPath - stmt_write_ebTx <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) - withDie $ DB.bindInt64 stmt_write_ebTx 2 (fromIntegral ebPoint) + stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) + withDie $ DB.bindInt64 stmt 2 (fromIntegral ebPoint) withDieMsg $ DB.exec db (fromString "BEGIN") -- decode incrementally and simultaneously UPDATE ebTxs -- @@ -515,10 +522,10 @@ msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do Just txBytes -> case offsets of [] -> die "Too many txs" txOffset:offsets' -> do - withDie $ DB.bindInt64 stmt_write_ebTx 3 $ fromIntegral txOffset - withDie $ DB.bindBlob stmt_write_ebTx 1 $ serialize' $ CBOR.encodeBytes txBytes - withDieDone $ DB.stepNoCB stmt_write_ebTx - withDie $ DB.reset stmt_write_ebTx + withDie $ DB.bindInt64 stmt 3 $ fromIntegral txOffset + withDie $ DB.bindBlob stmt 1 $ serialize' $ CBOR.encodeBytes txBytes + withDieDone $ DB.stepNoCB stmt + withDie $ DB.reset stmt go1 offsets' bytes Nothing | not (BSL.null bytes) -> die "Incomplete EB txs decode" From 7036dd263271bb6ddd4d02e11c6df6fca3f9301d Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 15 Oct 2025 10:27:10 -0700 Subject: [PATCH 026/119] leiosdemo202510: add fetch-decision and hash-txs commands --- ouroboros-consensus/app/leiosdemo202510.hs | 114 ++++++++++++++++++ ouroboros-consensus/ouroboros-consensus.cabal | 1 + 2 files changed, 115 insertions(+) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 955565e1f4..2e596a3611 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -19,14 +19,18 @@ import qualified Data.Bits as Bits import Data.ByteString (ByteString) import qualified Data.ByteString as BS import qualified Data.ByteString.Base16 as BS16 +import qualified Data.ByteString.Char8 as BS8 import qualified Data.ByteString.Lazy as BSL import Data.Foldable (forM_) +import qualified Data.IntMap as IntMap +import qualified Data.IntSet as IntSet import Data.List (intercalate, isSuffixOf, unfoldr) import Data.String (fromString) import qualified Data.Vector as V import Data.Word (Word8, Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB import GHC.Generics (Generic) +import qualified Numeric import System.Directory (doesFileExist) import System.Environment (getArgs) import System.Exit (die) @@ -78,11 +82,24 @@ main = getArgs >>= \case -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps + "fetch-decision" : dbPath : ebPointStrs + | ".db" `isSuffixOf` dbPath + , Just ebPoints <- sequence $ map readMaybe ebPointStrs + , not (null ebPoints) + -> do + db <- withDieMsg $ DB.open (fromString dbPath) + fetchDecision db (IntSet.fromList ebPoints) + ["hash-txs", ebTxsPath] + | ".bin" `isSuffixOf` ebTxsPath + -> do + hashTxs ebTxsPath _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ \ OR $0 MsgLeiosBlockRequest myDatabase.db ebPoint(int)\n\ \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) myEb.bin\n\ \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebPoint(int) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ \ OR $0 MsgLeiosBlockTxs myDatabase.db ebPoint(int) myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 fetch-decision myDatabase.db ebPoint(int) ebPoint(int) ebPoint(int) ...\n\ + \ OR $0 hash-txs myEbTxs.bin\n\ \" parseBitmaps :: [String] -> Maybe [(Word16, Word64)] @@ -549,3 +566,100 @@ sql_insert_ebTx = \SET txBytes = ?\n\ \WHERE ebPoint = ? AND txOffset = ? AND txBytes IS NULL\n\ \" + +----- + +_maxTxOffsetBitWidth :: Int +_maxTxOffsetBitWidth = ceiling $ log (fromIntegral maxEbItems :: Double) / log 2 + +maxRequestsPerIteration :: Int +maxRequestsPerIteration = 10 + +maxByteSizePerRequest :: Int +maxByteSizePerRequest = 500000 + +fetchDecision :: DB.Database -> IntSet.IntSet -> IO () +fetchDecision db ebPoints = do + stmt <- withDieJust $ DB.prepare db $ fromString $ sql_next_fetch (IntSet.size ebPoints) + forM_ ([(1 :: DB.ParamIndex) ..] `zip` IntSet.toDescList ebPoints) $ \(i, p) -> do + withDie $ DB.bindInt64 stmt i (fromIntegral p) + let loopLimit = maxRequestsPerIteration * maxByteSizePerRequest + loop !accReqs !accByteSize = + if accByteSize >= loopLimit then pure accReqs else + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> pure accReqs + DB.Row -> do + ebPoint <- fromIntegral <$> DB.columnInt64 stmt 0 + txOffset <- fromIntegral <$> DB.columnInt64 stmt 1 + txHash <- DB.columnBlob stmt 2 + txByteSize <- fromIntegral <$> DB.columnInt64 stmt 3 + loop + (IntMap.insertWith + IntMap.union + ebPoint + (IntMap.singleton txOffset txHash) + accReqs + ) + (accByteSize + txByteSize) + reqs <- loop IntMap.empty 0 + forM_ (IntMap.assocs reqs) $ \(ebPoint, m) -> do + let sho idx bitmap k = + if (0 :: Word64) == bitmap then k else + (show idx ++ ":0x" ++ Numeric.showHex bitmap "") : k + go idx bitmap = \case + [] -> sho idx bitmap [] + txOffset:txOffsets -> + let (q, r) = txOffset `quotRem` 64 + in + if q == idx + then go idx (Bits.setBit bitmap (63 - r)) txOffsets else + (if 0 /= bitmap then sho idx bitmap else id) + $ go q (Bits.bit (63 - r)) txOffsets + putStrLn + $ unwords + $ "bitmaps" : show ebPoint : go 0 (0x0 :: Word64) (IntMap.keys m) + putStrLn + $ unwords + $ "hashes" : show ebPoint : map (BS8.unpack . BS16.encode) (IntMap.elems m) + +-- | Arbitrarily limited to 2000; about 2000 average txs are in the ball park +-- of one megabyte. +-- +-- If a prefix of the 2000 txs are large, the fetch logic can ignore the rest. +-- +-- If all 2000 are still much less than a megabyte, then a) the EB is +-- suspicious and b) the fetch logic can advance the query (TODO require +-- parameterizing this query string with an OFFSET). +sql_next_fetch :: Int -> String +sql_next_fetch n = + "SELECT ebPoint, txOffset, txHashBytes, txByteSize FROM ebTxs\n\ + \WHERE txBytes IS NULL AND ebPoint IN (" ++ hooks ++ ")\n\ + \ORDER BY ebPoint DESC, txOffset ASC\n\ + \LIMIT 2000\n\ + \" + where + hooks = intercalate ", " (replicate n "?") + +----- + +hashTxs :: FilePath -> IO () +hashTxs ebTxsPath = do + ebTxsBytes <- BSL.readFile ebTxsPath + let decodeBreakOrTx = do + stop <- CBOR.decodeBreakOr + if stop then pure Nothing else Just <$> CBOR.decodeBytes + let go1 bytes = do + (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrTx bytes + go2 bytes bytes' next + go2 prevBytes bytes = \case + Just _txBytes -> do + let len = BSL.length prevBytes - BSL.length bytes + txHash :: Hash.Hash HASH ByteString + txHash = Hash.hashWith id $ BSL.toStrict $ BSL.take len prevBytes + putStrLn $ BS8.unpack $ BS16.encode $ Hash.hashToBytes txHash + go1 bytes + Nothing -> + when (not $ BSL.null bytes) $ do + die "Incomplete EB txs decode" + (ebTxsBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeListLenIndef ebTxsBytes + go1 ebTxsBytes2 diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 18ceb09b9d..b0b6189e7b 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -862,6 +862,7 @@ executable leiosdemo202510 cardano-binary, cardano-crypto-class, cborg, + containers, direct-sqlite, directory, random, From c9a6d68d626d2b6e62b0c8f0432650558095f9a0 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 15 Oct 2025 10:44:56 -0700 Subject: [PATCH 027/119] leiosdemo202510: only use "point" in the table name ebPoints --- ouroboros-consensus/app/leiosdemo202510.hs | 140 ++++++++++----------- 1 file changed, 70 insertions(+), 70 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 2e596a3611..b785664c63 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -53,52 +53,52 @@ main = getArgs >>= \case db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen generateDb prng0 db manifest - ["MsgLeiosBlockRequest", dbPath, ebPointStr] + ["MsgLeiosBlockRequest", dbPath, ebIdStr] | ".db" `isSuffixOf` dbPath - , Just ebPoint <- readMaybe ebPointStr + , Just ebId <- readMaybe ebIdStr -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockRequest db ebPoint - ["MsgLeiosBlock", dbPath, ebPointStr, ebSlotStr, ebPath] + msgLeiosBlockRequest db ebId + ["MsgLeiosBlock", dbPath, ebIdStr, ebSlotStr, ebPath] | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebPath - , Just ebPoint <- readMaybe ebPointStr + , Just ebId <- readMaybe ebIdStr , Just ebSlot <- readMaybe ebSlotStr -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlock db ebPoint ebSlot ebPath - "MsgLeiosBlockTxsRequest" : dbPath : ebPointStr : bitmapChunkStrs + msgLeiosBlock db ebId ebSlot ebPath + "MsgLeiosBlockTxsRequest" : dbPath : ebIdStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath - , Just ebPoint <- readMaybe ebPointStr + , Just ebId <- readMaybe ebIdStr , Just bitmaps <- parseBitmaps bitmapChunkStrs -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockTxsRequest db ebPoint bitmaps - "MsgLeiosBlockTxs" : dbPath : ebPointStr : ebTxsPath : bitmapChunkStrs + msgLeiosBlockTxsRequest db ebId bitmaps + "MsgLeiosBlockTxs" : dbPath : ebIdStr : ebTxsPath : bitmapChunkStrs | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebTxsPath - , Just ebPoint <- readMaybe ebPointStr + , Just ebId <- readMaybe ebIdStr , Just bitmaps <- parseBitmaps bitmapChunkStrs -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps - "fetch-decision" : dbPath : ebPointStrs + msgLeiosBlockTxs db ebId ebTxsPath bitmaps + "fetch-decision" : dbPath : ebIdStrs | ".db" `isSuffixOf` dbPath - , Just ebPoints <- sequence $ map readMaybe ebPointStrs - , not (null ebPoints) + , Just ebIds <- sequence $ map readMaybe ebIdStrs + , not (null ebIds) -> do db <- withDieMsg $ DB.open (fromString dbPath) - fetchDecision db (IntSet.fromList ebPoints) + fetchDecision db (IntSet.fromList ebIds) ["hash-txs", ebTxsPath] | ".bin" `isSuffixOf` ebTxsPath -> do hashTxs ebTxsPath _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ - \ OR $0 MsgLeiosBlockRequest myDatabase.db ebPoint(int)\n\ - \ OR $0 MsgLeiosBlock myDatabase.db ebPoint(int) myEb.bin\n\ - \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebPoint(int) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ - \ OR $0 MsgLeiosBlockTxs myDatabase.db ebPoint(int) myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ - \ OR $0 fetch-decision myDatabase.db ebPoint(int) ebPoint(int) ebPoint(int) ...\n\ + \ OR $0 MsgLeiosBlockRequest myDatabase.db ebId\n\ + \ OR $0 MsgLeiosBlock myDatabase.db ebId myEb.bin\n\ + \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebId index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlockTxs myDatabase.db ebId myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 fetch-decision myDatabase.db ebId ebId ebId ...\n\ \ OR $0 hash-txs myEbTxs.bin\n\ \" @@ -134,10 +134,10 @@ generateDb prng0 db ebRecipes = do gref <- R.newIOGenM prng0 -- init db withDieMsg $ DB.exec db (fromString sql_schema) - stmt_write_ebPoint <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoint) + stmt_write_ebId <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) - forM_ ([(0 :: Word16) ..] `zip` ebRecipes) $ \(ebPoint, ebRecipe) -> do + forM_ ([(0 :: Word16) ..] `zip` ebRecipes) $ \(ebId, ebRecipe) -> do -- generate txs, so we have their hashes txs <- V.forM (txByteSizes ebRecipe) $ \txByteSize -> do -- generate a random bytestring whose CBOR encoding has the expected length @@ -163,13 +163,13 @@ generateDb prng0 db ebRecipes = do (encodeEB (fromIntegral . BS.length) Hash.hashToBytes) txs withDieMsg $ DB.exec db (fromString "BEGIN") - withDie $ DB.bindInt64 stmt_write_ebPoint 3 (fromIntegral ebPoint) - withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegral ebId) -- INSERT INTO ebPoints - withDie $ DB.bindInt64 stmt_write_ebPoint 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_write_ebPoint 2 (Hash.hashToBytes ebHash) - withDieDone $ DB.stepNoCB stmt_write_ebPoint - withDie $ DB.reset stmt_write_ebPoint + withDie $ DB.bindInt64 stmt_write_ebId 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_write_ebId 2 (Hash.hashToBytes ebHash) + withDieDone $ DB.stepNoCB stmt_write_ebId + withDie $ DB.reset stmt_write_ebId -- loop over txs V.iforM_ txs $ \txOffset (txBytes, txHash) -> do -- INSERT INTO ebTxs @@ -201,13 +201,13 @@ sql_schema = \ ,\n\ \ ebHash BLOB NOT NULL\n\ \ ,\n\ - \ id INTEGER NOT NULL\n\ + \ ebId INTEGER NOT NULL\n\ \ ,\n\ \ PRIMARY KEY (ebSlot, ebHash)\n\ \ ) WITHOUT ROWID;\n\ \\n\ \CREATE TABLE ebTxs (\n\ - \ ebPoint INTEGER NOT NULL -- foreign key ebPoints.id\n\ + \ ebId INTEGER NOT NULL -- foreign key ebPoints.ebId\n\ \ ,\n\ \ txOffset INTEGER NOT NULL\n\ \ ,\n\ @@ -217,35 +217,35 @@ sql_schema = \ ,\n\ \ txBytes BLOB -- valid CBOR\n\ \ ,\n\ - \ PRIMARY KEY (ebPoint, txOffset)\n\ + \ PRIMARY KEY (ebId, txOffset)\n\ \ ) WITHOUT ROWID;\n\ \" sql_index_schema :: String sql_index_schema = "CREATE INDEX ebPointsExpiry\n\ - \ ON ebPoints (ebSlot, id); -- Helps with the eviction policy of the EbStore.\n\ + \ ON ebPoints (ebSlot, ebId); -- Helps with the eviction policy of the EbStore.\n\ \\n\ \CREATE INDEX txCacheExpiry\n\ \ ON txCache (expiryUnixEpoch, txHashBytes); -- Helps with the eviction policy of the TxCache.\n\ \\n\ \CREATE INDEX missingEbTxs\n\ - \ ON ebTxs (ebPoint, txOffset)\n\ + \ ON ebTxs (ebId, txOffset)\n\ \ WHERE txBytes IS NULL; -- Helps with fetch logic decisions.\n\ \\n\ \CREATE INDEX acquiredEbTxs\n\ - \ ON ebTxs (ebPoint, txOffset)\n\ + \ ON ebTxs (ebId, txOffset)\n\ \ WHERE txBytes IS NOT NULL; -- Helps with fetch logic decisions.\n\ \" -sql_insert_ebPoint :: String -sql_insert_ebPoint = - "INSERT INTO ebPoints (ebSlot, ebHash, id) VALUES (?, ?, ?)\n\ +sql_insert_ebId :: String +sql_insert_ebId = + "INSERT INTO ebPoints (ebSlot, ebHash, ebId) VALUES (?, ?, ?)\n\ \" sql_insert_ebClosure :: String sql_insert_ebClosure = - "INSERT INTO ebTxs (ebPoint, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ + "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ \" ----- @@ -321,10 +321,10 @@ pushX (X n xs vs) x = X 1 [x] (V.fromList xs : vs) msgLeiosBlockRequest :: DB.Database -> Int -> IO () -msgLeiosBlockRequest db ebPoint = do +msgLeiosBlockRequest db ebId = do -- get the EB items stmt <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) - withDie $ DB.bindInt64 stmt 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt 1 (fromIntegral ebId) let loop !acc = withDie (DB.stepNoCB stmt) >>= \case DB.Done -> pure acc @@ -346,12 +346,12 @@ msgLeiosBlockRequest db ebPoint = do sql_lookup_ebBodies_DESC :: String sql_lookup_ebBodies_DESC = "SELECT txHashBytes, txByteSize FROM ebTxs\n\ - \WHERE ebPoint = ?\n\ + \WHERE ebId = ?\n\ \ORDER BY txOffset DESC\n\ \" msgLeiosBlockTxsRequest :: DB.Database -> Int -> [(Word16, Word64)] -> IO () -msgLeiosBlockTxsRequest db ebPoint bitmaps = do +msgLeiosBlockTxsRequest db ebId bitmaps = do do let idxs = map fst bitmaps let idxLimit = maxEbItems `div` 64 @@ -373,7 +373,7 @@ msgLeiosBlockTxsRequest db ebPoint bitmaps = do -- -- TODO Better workaround for requests of many txs? stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (maxBatchSize `min` numOffsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebId) withDieMsg $ DB.exec db (fromString "BEGIN") acc <- (\f -> foldM f emptyX (batches offsets)) $ \acc batch -> do stmt <- @@ -381,7 +381,7 @@ msgLeiosBlockTxsRequest db ebPoint bitmaps = do -- this can only be reached for the last batch withDie $ DB.finalize stmt_lookup_ebClosuresMAIN stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (numOffsets `mod` maxBatchSize) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebId) pure stmt_lookup_ebClosuresTIDY forM_ ([(2 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do withDie $ DB.bindInt64 stmt i (fromIntegral offset) @@ -468,7 +468,7 @@ batches xs = if null xs then [] else take maxBatchSize xs : batches (drop maxBat sql_lookup_ebClosures_DESC :: Int -> String sql_lookup_ebClosures_DESC n = "SELECT txOffset, txBytes FROM ebTxs\n\ - \WHERE ebPoint = ? AND txBytes IS NOT NULL AND txOffset IN (" ++ hooks ++ ")\n\ + \WHERE ebId = ? AND txBytes IS NOT NULL AND txOffset IN (" ++ hooks ++ ")\n\ \ORDER BY txOffset DESC\n\ \" where @@ -476,23 +476,23 @@ sql_lookup_ebClosures_DESC n = ----- --- | PREREQ: No row in ebTxs already has this ebPoint. +-- | PREREQ: No row in ebTxs already has this ebId. msgLeiosBlock :: DB.Database -> Int -> Word64 -> FilePath -> IO () -msgLeiosBlock db ebPoint ebSlot ebPath = do +msgLeiosBlock db ebId ebSlot ebPath = do ebBytes <- BS.readFile ebPath let ebHash :: Hash.Hash HASH ByteString ebHash = Hash.castHash $ Hash.hashWith id ebBytes - stmt_write_ebPoints <- withDieJust $ DB.prepare db (fromString sql_insert_ebPoint) + stmt_write_ebIds <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) withDieMsg $ DB.exec db (fromString "BEGIN") -- INSERT INTO ebPoints - withDie $ DB.bindInt64 stmt_write_ebPoints 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_write_ebPoints 2 (Hash.hashToBytes ebHash) - withDie $ DB.bindInt64 stmt_write_ebPoints 3 (fromIntegral ebPoint) - withDieDone $ DB.stepNoCB stmt_write_ebPoints - withDie $ DB.reset stmt_write_ebPoints + withDie $ DB.bindInt64 stmt_write_ebIds 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_write_ebIds 2 (Hash.hashToBytes ebHash) + withDie $ DB.bindInt64 stmt_write_ebIds 3 (fromIntegral ebId) + withDieDone $ DB.stepNoCB stmt_write_ebIds + withDie $ DB.reset stmt_write_ebIds -- decode incrementally and simultaneously INSERT INTO ebTxs - withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegral ebId) let decodeBreakOrEbPair = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> decodeEbPair @@ -517,14 +517,14 @@ msgLeiosBlock db ebPoint ebSlot ebPath = do sql_insert_ebBody :: String sql_insert_ebBody = - "INSERT INTO ebTxs (ebPoint, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ + "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ \" msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () -msgLeiosBlockTxs db ebPoint ebTxsPath bitmaps = do +msgLeiosBlockTxs db ebId ebTxsPath bitmaps = do ebTxsBytes <- BSL.readFile ebTxsPath stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) - withDie $ DB.bindInt64 stmt 2 (fromIntegral ebPoint) + withDie $ DB.bindInt64 stmt 2 (fromIntegral ebId) withDieMsg $ DB.exec db (fromString "BEGIN") -- decode incrementally and simultaneously UPDATE ebTxs -- @@ -564,7 +564,7 @@ sql_insert_ebTx :: String sql_insert_ebTx = "UPDATE ebTxs\n\ \SET txBytes = ?\n\ - \WHERE ebPoint = ? AND txOffset = ? AND txBytes IS NULL\n\ + \WHERE ebId = ? AND txOffset = ? AND txBytes IS NULL\n\ \" ----- @@ -579,9 +579,9 @@ maxByteSizePerRequest :: Int maxByteSizePerRequest = 500000 fetchDecision :: DB.Database -> IntSet.IntSet -> IO () -fetchDecision db ebPoints = do - stmt <- withDieJust $ DB.prepare db $ fromString $ sql_next_fetch (IntSet.size ebPoints) - forM_ ([(1 :: DB.ParamIndex) ..] `zip` IntSet.toDescList ebPoints) $ \(i, p) -> do +fetchDecision db ebIds = do + stmt <- withDieJust $ DB.prepare db $ fromString $ sql_next_fetch (IntSet.size ebIds) + forM_ ([(1 :: DB.ParamIndex) ..] `zip` IntSet.toDescList ebIds) $ \(i, p) -> do withDie $ DB.bindInt64 stmt i (fromIntegral p) let loopLimit = maxRequestsPerIteration * maxByteSizePerRequest loop !accReqs !accByteSize = @@ -589,20 +589,20 @@ fetchDecision db ebPoints = do withDie (DB.stepNoCB stmt) >>= \case DB.Done -> pure accReqs DB.Row -> do - ebPoint <- fromIntegral <$> DB.columnInt64 stmt 0 + ebId <- fromIntegral <$> DB.columnInt64 stmt 0 txOffset <- fromIntegral <$> DB.columnInt64 stmt 1 txHash <- DB.columnBlob stmt 2 txByteSize <- fromIntegral <$> DB.columnInt64 stmt 3 loop (IntMap.insertWith IntMap.union - ebPoint + ebId (IntMap.singleton txOffset txHash) accReqs ) (accByteSize + txByteSize) reqs <- loop IntMap.empty 0 - forM_ (IntMap.assocs reqs) $ \(ebPoint, m) -> do + forM_ (IntMap.assocs reqs) $ \(ebId, m) -> do let sho idx bitmap k = if (0 :: Word64) == bitmap then k else (show idx ++ ":0x" ++ Numeric.showHex bitmap "") : k @@ -617,10 +617,10 @@ fetchDecision db ebPoints = do $ go q (Bits.bit (63 - r)) txOffsets putStrLn $ unwords - $ "bitmaps" : show ebPoint : go 0 (0x0 :: Word64) (IntMap.keys m) + $ "bitmaps" : show ebId : go 0 (0x0 :: Word64) (IntMap.keys m) putStrLn $ unwords - $ "hashes" : show ebPoint : map (BS8.unpack . BS16.encode) (IntMap.elems m) + $ "hashes" : show ebId : map (BS8.unpack . BS16.encode) (IntMap.elems m) -- | Arbitrarily limited to 2000; about 2000 average txs are in the ball park -- of one megabyte. @@ -632,9 +632,9 @@ fetchDecision db ebPoints = do -- parameterizing this query string with an OFFSET). sql_next_fetch :: Int -> String sql_next_fetch n = - "SELECT ebPoint, txOffset, txHashBytes, txByteSize FROM ebTxs\n\ - \WHERE txBytes IS NULL AND ebPoint IN (" ++ hooks ++ ")\n\ - \ORDER BY ebPoint DESC, txOffset ASC\n\ + "SELECT ebId, txOffset, txHashBytes, txByteSize FROM ebTxs\n\ + \WHERE txBytes IS NULL AND ebId IN (" ++ hooks ++ ")\n\ + \ORDER BY ebId DESC, txOffset ASC\n\ \LIMIT 2000\n\ \" where From 1c2a031ed4abc5a64f9ded799e9415d0e2ceaff2 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 15 Oct 2025 10:50:36 -0700 Subject: [PATCH 028/119] leiosdemo202510: add some of the missing Haddock --- ouroboros-consensus/app/leiosdemo202510.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index b785664c63..5a4c488646 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -293,6 +293,7 @@ decodeEbPair :: CBOR.Decoder s (ByteString, Word16) decodeEbPair = (,) <$> CBOR.decodeBytes <*> CBOR.decodeWord16 +-- | The logic in this module instead does this decoding incrementally _decodeEB :: CBOR.Decoder s (X (ByteString, Word16)) _decodeEB = CBOR.decodeMapLenIndef @@ -304,11 +305,14 @@ _decodeEB = ----- --- | helper for msgLeiosBlockRequest +-- | helper for msgLeiosBlockRequest and msgLeiosBlockTxsRequest -- -- The @[a]@ is less than 1024 long. -- -- Each 'V.Vector' is exactly 1024 long. +-- +-- TODO those functions could instead generate the CBOR incrementally, but will +-- the patched node be able to do that? data X a = X !Word16 [a] [V.Vector a] deriving (Functor, Foldable) @@ -455,8 +459,8 @@ popRightmostOffset = \case -- | Never request more than this many txs simultaneously -- --- TODO confirm this prevents the query string from exceeding its size limits, --- even if the largest txOffsets are being requested. +-- TODO confirm this prevents the query string from exceeding SQLite's size +-- limits, even if the largest possible txOffsets are being requested. maxBatchSize :: Int maxBatchSize = 1024 @@ -476,7 +480,9 @@ sql_lookup_ebClosures_DESC n = ----- --- | PREREQ: No row in ebTxs already has this ebId. +-- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlock +-- +-- PREREQ: No row in ebTxs already has this ebId. msgLeiosBlock :: DB.Database -> Int -> Word64 -> FilePath -> IO () msgLeiosBlock db ebId ebSlot ebPath = do ebBytes <- BS.readFile ebPath @@ -520,6 +526,7 @@ sql_insert_ebBody = "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ \" +-- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlockTxs msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () msgLeiosBlockTxs db ebId ebTxsPath bitmaps = do ebTxsBytes <- BSL.readFile ebTxsPath @@ -642,6 +649,7 @@ sql_next_fetch n = ----- +-- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlockTxs hashTxs :: FilePath -> IO () hashTxs ebTxsPath = do ebTxsBytes <- BSL.readFile ebTxsPath From 41358c1679680ca9ba458364f41b56eeb4155534 Mon Sep 17 00:00:00 2001 From: dnadales Date: Mon, 20 Oct 2025 16:26:03 -0300 Subject: [PATCH 029/119] Add a script to analyze the two node log files Calculates the propagation latency for each block by measuring the time difference between the completion of the block fetch on the upstream node (node 0) and the completion of the block fetch on the downstream node (node 1). --- scripts/leios-demo/log_parser.py | 191 +++++++++++++++++++++++++++++++ 1 file changed, 191 insertions(+) create mode 100644 scripts/leios-demo/log_parser.py diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py new file mode 100644 index 0000000000..6e48d7a73a --- /dev/null +++ b/scripts/leios-demo/log_parser.py @@ -0,0 +1,191 @@ +import os +import sys +import json +import pandas as pd +import numpy as np + +# --- Configuration --- +# Filter for the event containing the timestamp we want to measure at node 0 and node 1 +BLOCK_EVENT_FILTER = 'BlockFetch.Client.CompletedBlockFetch' +# Filter for the event containing the slot and hash. We need to do this because the 'CompletedBlockFetch' event does not contain the slot number. +HEADER_EVENT_FILTER = 'ChainSync.Client.DownloadedHeader' + +def filter_log_events(log_path: str, filter_text: str): + """ + Reads a log file, parses JSON lines, and extracts relevant fields + based on the filter type. + """ + log_filename = os.path.basename(log_path) + print(f"\n--- Analyzing Log: {log_filename} for event: '{filter_text}' ---") + + parsed_data = [] + + try: + with open(log_path, 'r') as f: + for line in f: + try: + log_entry = json.loads(line) + + # Check if the namespace matches the filter + if log_entry.get('ns') == filter_text: + + event_data = log_entry.get('data', {}) + block_hash = None + block_slot = None + + # Determine extraction logic based on the event type + if filter_text == HEADER_EVENT_FILTER: + # Structure: "data":{"block": "HASH", ..., "slot": SLOT} + block_hash = event_data.get('block') + block_slot = event_data.get('slot') + elif filter_text == BLOCK_EVENT_FILTER: + # Structure: "data":{"block": "HASH", ...} + block_hash = event_data.get('block') + block_slot = None + + # Base record structure + record = { + 'node': log_filename.split('-')[-1].split('.')[0], + 'at': log_entry.get('at'), + 'hash': block_hash, + 'slot': block_slot, + } + + # Only add if the core fields were successfully extracted + if record['at'] and record['hash']: + parsed_data.append(record) + + except json.JSONDecodeError: + continue + except Exception as e: + # This catch remains for general unexpected issues. + print(f"Warning: Failed to parse or extract fields from a line in {log_filename}. Error: {e}", file=sys.stderr) + continue + + print(f"Successfully extracted {len(parsed_data)} records matching '{filter_text}'.") + return parsed_data + + except FileNotFoundError: + print(f"Error: Log file not found at {log_path}.", file=sys.stderr) + return [] + except Exception as e: + print(f"An unexpected error occurred while processing {log_path}: {e}", file=sys.stderr) + return [] + +def create_and_clean_df(records: list, node_id: str, timestamp_column: str, unique_subset: list) -> pd.DataFrame: + """ + Converts records to a DataFrame, converts types, removes duplicates, + and renames the 'at' column. + """ + if not records: + # Return an empty DataFrame with the expected columns if no records were found. + # This prevents KeyError later during column selection. + return pd.DataFrame(columns=['hash', 'slot', 'at', 'node']).rename(columns={'at': timestamp_column}) + + + df = pd.DataFrame(records) + + # Convert columns to appropriate data types + try: + if 'at' in df.columns: + df['at'] = pd.to_datetime(df['at']) + if 'slot' in df.columns: + df['slot'] = pd.to_numeric(df['slot'], errors='coerce').astype('Int64') + except Exception as e: + print(f"Warning: Failed to convert data types in DataFrame for node {node_id}: {e}", file=sys.stderr) + return pd.DataFrame(columns=['hash', 'slot', 'at', 'node']).rename(columns={'at': timestamp_column}) + + + # Deduplication: Keep only the first (earliest) occurrence + initial_rows = len(df) + df = df.sort_values(by='at' if 'at' in df.columns else df.columns[0]).drop_duplicates(subset=unique_subset, keep='first') + + if len(df) < initial_rows: + duplicates_removed = initial_rows - len(df) + print(f"Warning: Removed {duplicates_removed} duplicate log entries from node {node_id}.") + + # Rename the timestamp column for merging later + if 'at' in df.columns: + df = df.rename(columns={'at': timestamp_column}) + + return df + + +if __name__ == "__main__": + if len(sys.argv) != 3: + print("Configuration Error: Please provide the full path to exactly TWO log files.", file=sys.stderr) + print("Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", file=sys.stderr) + sys.exit(1) + + log_path_0 = sys.argv[1] + log_path_1 = sys.argv[2] + + # --- STEP 1: Create Hash-to-Slot Lookup Table (Headers) --- + + # Collect header data from node 0 only (the primary source for slot mapping) + header_data = filter_log_events(log_path_0, HEADER_EVENT_FILTER) + + if not header_data: + print("\nNo header events found for slot/hash lookup. Exiting.") + sys.exit(0) + + # Create the header lookup DataFrame + df_headers_full = create_and_clean_df(header_data, '0', 'at_header_lookup', ['slot', 'hash', 'node']) + + # Select only the necessary lookup columns and drop any entries where slot is still None + df_headers = df_headers_full[['hash', 'slot']].dropna(subset=['slot']).drop_duplicates(subset=['hash'], keep='first') + print(f"Created Hash-to-Slot lookup table with {len(df_headers)} unique entries.") + + + # --- STEP 2: Collect and Process Block Fetch Timestamps --- + + # Node 0 Block Fetch Data + raw_data_0 = filter_log_events(log_path_0, BLOCK_EVENT_FILTER) + df_node_0_block = create_and_clean_df(raw_data_0, '0', 'at_node_0', ['hash', 'node']) + + # Node 1 Block Fetch Data + raw_data_1 = filter_log_events(log_path_1, BLOCK_EVENT_FILTER) + df_node_1_block = create_and_clean_df(raw_data_1, '1', 'at_node_1', ['hash', 'node']) + + # --- STEP 3: Inject Slot Number into Block Fetch Data --- + + # Inject 'slot' into Node 0 data using 'hash' + df_node_0_final = pd.merge( + df_node_0_block[['hash', 'at_node_0']], + df_headers, + on='hash', + how='inner' + ) + + # Inject 'slot' into Node 1 data using 'hash' + df_node_1_final = pd.merge( + df_node_1_block[['hash', 'at_node_1']], + df_headers, + on='hash', + how='inner' + ) + + + # --- STEP 4: Final Merge on Hash AND Slot --- + + if df_node_0_final.empty or df_node_1_final.empty: + print("\nCould not match block fetch times to slot numbers for one or both nodes. Exiting.") + sys.exit(0) + + # Final merge to compare the two nodes for the same block + df_merged = pd.merge( + df_node_0_final, + df_node_1_final, + on=['hash', 'slot'], + how='inner', + ) + + + # --- STEP 5: Calculate Latency (Time Difference) --- + df_merged['latency_ms'] = (df_merged['at_node_1'] - df_merged['at_node_0']).dt.total_seconds() * 1000 + + + print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") + print("Each row represents a unique block seen by both nodes, joined by hash and slot.") + print(df_merged.head()) + print(f"\nTotal unique block events matched: {len(df_merged)}") From 31c21cf6d02896b2ba5d5b7cf05ddc6145a1d6a6 Mon Sep 17 00:00:00 2001 From: dnadales Date: Mon, 20 Oct 2025 17:43:14 -0300 Subject: [PATCH 030/119] Hook the python script to the demo script --- scripts/leios-demo/leios-october-demo.sh | 57 +++++++++++++++++------- 1 file changed, 40 insertions(+), 17 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 09e7fb7907..23f66c7927 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -32,21 +32,6 @@ fi TMP_DIR=$(mktemp -d) echo "Using temporary directory for DB and logs: $TMP_DIR" -## -## Run immdb-server -## -IMMDB_CMD_CORE="cabal run immdb-server \ - -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ - --config $CLUSTER_RUN_DATA/node-0/config.json" - -echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" - -$IMMDB_CMD_CORE &> "$TMP_DIR/immdb-server.log" & - -IMMDB_SERVER_PID=$! - -echo "ImmDB server started with PID: $IMMDB_SERVER_PID" - pushd "$CARDANO_NODE_PATH" > /dev/null ## @@ -135,10 +120,30 @@ echo "Cardano node 1 started with PID: $MOCKED_PEER_PID" # Return to the original directory popd > /dev/null -# TODO: we should change the condition on which we terminate the demo. -echo "Sleeping for 30 seconds" +## +## Run immdb-server +## + +## TODO: we should find a better way to wait for the nodes to be started sleep 30 +IMMDB_CMD_CORE="cabal run immdb-server \ + -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ + --config $CLUSTER_RUN_DATA/node-0/config.json" + +echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" + +$IMMDB_CMD_CORE &> "$TMP_DIR/immdb-server.log" & + +IMMDB_SERVER_PID=$! + +echo "ImmDB server started with PID: $IMMDB_SERVER_PID" + + +# TODO: we should change the condition on which we terminate the demo. +echo "Sleeping..." +sleep 120 + echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." kill "$IMMDB_SERVER_PID" 2>/dev/null || true @@ -149,4 +154,22 @@ kill -9 -"$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" +# Log analysis + +VENV_PATH="./scripts/leios-demo/venv" + +# 1. Activate the Python Virtual Environment +if [ -f "$VENV_PATH/bin/activate" ]; then + echo "Activating virtual environment..." + # 'source' must be used for activation to modify the current shell environment + source "$VENV_PATH/bin/activate" +else + echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 +fi + +python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log + +# 2. Deactivate the Python Virtual Environment before exiting +deactivate 2>/dev/null || true + exit 0 From daaf2ea98e464cb326469af574ac7f2e1f6a8bf7 Mon Sep 17 00:00:00 2001 From: dnadales Date: Mon, 20 Oct 2025 17:59:28 -0300 Subject: [PATCH 031/119] Add requirements.txt for log_parser.py --- requirements.txt | 14 ++++++++++++++ 1 file changed, 14 insertions(+) create mode 100644 requirements.txt diff --git a/requirements.txt b/requirements.txt new file mode 100644 index 0000000000..56552f0d9f --- /dev/null +++ b/requirements.txt @@ -0,0 +1,14 @@ +contourpy==1.3.3 +cycler==0.12.1 +fonttools==4.60.1 +kiwisolver==1.4.9 +matplotlib==3.10.7 +numpy==2.3.4 +packaging==25.0 +pandas==2.3.3 +pillow==12.0.0 +pyparsing==3.2.5 +python-dateutil==2.9.0.post0 +pytz==2025.2 +six==1.17.0 +tzdata==2025.2 From 2b7cbe969e0ee3ddc91113e5094c72041a190278 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 21 Oct 2025 16:29:32 +0200 Subject: [PATCH 032/119] Nixify the Leios demo environment --- flake.nix | 3 ++- scripts/leios-demo/.envrc | 1 + scripts/leios-demo/build.nix | 26 +++++++++++++++++++ .../leios-demo/requirements.txt | 0 4 files changed, 29 insertions(+), 1 deletion(-) create mode 100644 scripts/leios-demo/.envrc create mode 100644 scripts/leios-demo/build.nix rename requirements.txt => scripts/leios-demo/requirements.txt (100%) diff --git a/flake.nix b/flake.nix index 948778cda4..9dae47b55d 100644 --- a/flake.nix +++ b/flake.nix @@ -69,6 +69,7 @@ ]; }; hydraJobs = import ./nix/ci.nix { inherit inputs pkgs; }; + leiosDemo = import ./scripts/leios-demo/build.nix { inherit inputs pkgs; }; in { devShells = rec { @@ -83,7 +84,7 @@ website = pkgs.mkShell { packages = [ pkgs.nodejs pkgs.yarn ]; }; - }; + } // leiosDemo.devShells; inherit hydraJobs; legacyPackages = pkgs; packages = diff --git a/scripts/leios-demo/.envrc b/scripts/leios-demo/.envrc new file mode 100644 index 0000000000..1c4ca89416 --- /dev/null +++ b/scripts/leios-demo/.envrc @@ -0,0 +1 @@ +use flake .#devLeiosDemo diff --git a/scripts/leios-demo/build.nix b/scripts/leios-demo/build.nix new file mode 100644 index 0000000000..882d4f68ee --- /dev/null +++ b/scripts/leios-demo/build.nix @@ -0,0 +1,26 @@ +{ pkgs, inputs, ... }: +{ + + devShells = { + devLeiosDemo = pkgs.mkShell { + name = "leios-demo"; + buildInputs = with pkgs; with python3Packages; + [ + python3 + ipython + pandas + pip + virtualenv + python-lsp-server + jupyterlab + black + + nixpkgs-fmt + nil + + shellcheck + ]; + }; + }; + +} diff --git a/requirements.txt b/scripts/leios-demo/requirements.txt similarity index 100% rename from requirements.txt rename to scripts/leios-demo/requirements.txt From 7bd63e1699b3d596817655a4a1e53678b5e0b192 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 21 Oct 2025 16:30:10 +0200 Subject: [PATCH 033/119] Appliy black python formatter --- scripts/leios-demo/log_parser.py | 139 +++++++++++++++++++------------ 1 file changed, 86 insertions(+), 53 deletions(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 6e48d7a73a..4e681858ee 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -6,9 +6,10 @@ # --- Configuration --- # Filter for the event containing the timestamp we want to measure at node 0 and node 1 -BLOCK_EVENT_FILTER = 'BlockFetch.Client.CompletedBlockFetch' +BLOCK_EVENT_FILTER = "BlockFetch.Client.CompletedBlockFetch" # Filter for the event containing the slot and hash. We need to do this because the 'CompletedBlockFetch' event does not contain the slot number. -HEADER_EVENT_FILTER = 'ChainSync.Client.DownloadedHeader' +HEADER_EVENT_FILTER = "ChainSync.Client.DownloadedHeader" + def filter_log_events(log_path: str, filter_text: str): """ @@ -21,58 +22,69 @@ def filter_log_events(log_path: str, filter_text: str): parsed_data = [] try: - with open(log_path, 'r') as f: + with open(log_path, "r") as f: for line in f: try: log_entry = json.loads(line) # Check if the namespace matches the filter - if log_entry.get('ns') == filter_text: + if log_entry.get("ns") == filter_text: - event_data = log_entry.get('data', {}) + event_data = log_entry.get("data", {}) block_hash = None block_slot = None # Determine extraction logic based on the event type if filter_text == HEADER_EVENT_FILTER: # Structure: "data":{"block": "HASH", ..., "slot": SLOT} - block_hash = event_data.get('block') - block_slot = event_data.get('slot') + block_hash = event_data.get("block") + block_slot = event_data.get("slot") elif filter_text == BLOCK_EVENT_FILTER: # Structure: "data":{"block": "HASH", ...} - block_hash = event_data.get('block') + block_hash = event_data.get("block") block_slot = None # Base record structure record = { - 'node': log_filename.split('-')[-1].split('.')[0], - 'at': log_entry.get('at'), - 'hash': block_hash, - 'slot': block_slot, + "node": log_filename.split("-")[-1].split(".")[0], + "at": log_entry.get("at"), + "hash": block_hash, + "slot": block_slot, } # Only add if the core fields were successfully extracted - if record['at'] and record['hash']: + if record["at"] and record["hash"]: parsed_data.append(record) except json.JSONDecodeError: continue except Exception as e: # This catch remains for general unexpected issues. - print(f"Warning: Failed to parse or extract fields from a line in {log_filename}. Error: {e}", file=sys.stderr) + print( + f"Warning: Failed to parse or extract fields from a line in {log_filename}. Error: {e}", + file=sys.stderr, + ) continue - print(f"Successfully extracted {len(parsed_data)} records matching '{filter_text}'.") + print( + f"Successfully extracted {len(parsed_data)} records matching '{filter_text}'." + ) return parsed_data except FileNotFoundError: print(f"Error: Log file not found at {log_path}.", file=sys.stderr) return [] except Exception as e: - print(f"An unexpected error occurred while processing {log_path}: {e}", file=sys.stderr) + print( + f"An unexpected error occurred while processing {log_path}: {e}", + file=sys.stderr, + ) return [] -def create_and_clean_df(records: list, node_id: str, timestamp_column: str, unique_subset: list) -> pd.DataFrame: + +def create_and_clean_df( + records: list, node_id: str, timestamp_column: str, unique_subset: list +) -> pd.DataFrame: """ Converts records to a DataFrame, converts types, removes duplicates, and renames the 'at' column. @@ -80,41 +92,56 @@ def create_and_clean_df(records: list, node_id: str, timestamp_column: str, uniq if not records: # Return an empty DataFrame with the expected columns if no records were found. # This prevents KeyError later during column selection. - return pd.DataFrame(columns=['hash', 'slot', 'at', 'node']).rename(columns={'at': timestamp_column}) - + return pd.DataFrame(columns=["hash", "slot", "at", "node"]).rename( + columns={"at": timestamp_column} + ) df = pd.DataFrame(records) # Convert columns to appropriate data types try: - if 'at' in df.columns: - df['at'] = pd.to_datetime(df['at']) - if 'slot' in df.columns: - df['slot'] = pd.to_numeric(df['slot'], errors='coerce').astype('Int64') + if "at" in df.columns: + df["at"] = pd.to_datetime(df["at"]) + if "slot" in df.columns: + df["slot"] = pd.to_numeric(df["slot"], errors="coerce").astype("Int64") except Exception as e: - print(f"Warning: Failed to convert data types in DataFrame for node {node_id}: {e}", file=sys.stderr) - return pd.DataFrame(columns=['hash', 'slot', 'at', 'node']).rename(columns={'at': timestamp_column}) - + print( + f"Warning: Failed to convert data types in DataFrame for node {node_id}: {e}", + file=sys.stderr, + ) + return pd.DataFrame(columns=["hash", "slot", "at", "node"]).rename( + columns={"at": timestamp_column} + ) # Deduplication: Keep only the first (earliest) occurrence initial_rows = len(df) - df = df.sort_values(by='at' if 'at' in df.columns else df.columns[0]).drop_duplicates(subset=unique_subset, keep='first') + df = df.sort_values( + by="at" if "at" in df.columns else df.columns[0] + ).drop_duplicates(subset=unique_subset, keep="first") if len(df) < initial_rows: duplicates_removed = initial_rows - len(df) - print(f"Warning: Removed {duplicates_removed} duplicate log entries from node {node_id}.") + print( + f"Warning: Removed {duplicates_removed} duplicate log entries from node {node_id}." + ) # Rename the timestamp column for merging later - if 'at' in df.columns: - df = df.rename(columns={'at': timestamp_column}) + if "at" in df.columns: + df = df.rename(columns={"at": timestamp_column}) return df if __name__ == "__main__": if len(sys.argv) != 3: - print("Configuration Error: Please provide the full path to exactly TWO log files.", file=sys.stderr) - print("Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", file=sys.stderr) + print( + "Configuration Error: Please provide the full path to exactly TWO log files.", + file=sys.stderr, + ) + print( + "Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", + file=sys.stderr, + ) sys.exit(1) log_path_0 = sys.argv[1] @@ -130,62 +157,68 @@ def create_and_clean_df(records: list, node_id: str, timestamp_column: str, uniq sys.exit(0) # Create the header lookup DataFrame - df_headers_full = create_and_clean_df(header_data, '0', 'at_header_lookup', ['slot', 'hash', 'node']) + df_headers_full = create_and_clean_df( + header_data, "0", "at_header_lookup", ["slot", "hash", "node"] + ) # Select only the necessary lookup columns and drop any entries where slot is still None - df_headers = df_headers_full[['hash', 'slot']].dropna(subset=['slot']).drop_duplicates(subset=['hash'], keep='first') + df_headers = ( + df_headers_full[["hash", "slot"]] + .dropna(subset=["slot"]) + .drop_duplicates(subset=["hash"], keep="first") + ) print(f"Created Hash-to-Slot lookup table with {len(df_headers)} unique entries.") - # --- STEP 2: Collect and Process Block Fetch Timestamps --- # Node 0 Block Fetch Data raw_data_0 = filter_log_events(log_path_0, BLOCK_EVENT_FILTER) - df_node_0_block = create_and_clean_df(raw_data_0, '0', 'at_node_0', ['hash', 'node']) + df_node_0_block = create_and_clean_df( + raw_data_0, "0", "at_node_0", ["hash", "node"] + ) # Node 1 Block Fetch Data raw_data_1 = filter_log_events(log_path_1, BLOCK_EVENT_FILTER) - df_node_1_block = create_and_clean_df(raw_data_1, '1', 'at_node_1', ['hash', 'node']) + df_node_1_block = create_and_clean_df( + raw_data_1, "1", "at_node_1", ["hash", "node"] + ) # --- STEP 3: Inject Slot Number into Block Fetch Data --- # Inject 'slot' into Node 0 data using 'hash' df_node_0_final = pd.merge( - df_node_0_block[['hash', 'at_node_0']], - df_headers, - on='hash', - how='inner' + df_node_0_block[["hash", "at_node_0"]], df_headers, on="hash", how="inner" ) # Inject 'slot' into Node 1 data using 'hash' df_node_1_final = pd.merge( - df_node_1_block[['hash', 'at_node_1']], - df_headers, - on='hash', - how='inner' + df_node_1_block[["hash", "at_node_1"]], df_headers, on="hash", how="inner" ) - # --- STEP 4: Final Merge on Hash AND Slot --- if df_node_0_final.empty or df_node_1_final.empty: - print("\nCould not match block fetch times to slot numbers for one or both nodes. Exiting.") + print( + "\nCould not match block fetch times to slot numbers for one or both nodes. Exiting." + ) sys.exit(0) # Final merge to compare the two nodes for the same block df_merged = pd.merge( df_node_0_final, df_node_1_final, - on=['hash', 'slot'], - how='inner', + on=["hash", "slot"], + how="inner", ) - # --- STEP 5: Calculate Latency (Time Difference) --- - df_merged['latency_ms'] = (df_merged['at_node_1'] - df_merged['at_node_0']).dt.total_seconds() * 1000 - + df_merged["latency_ms"] = ( + df_merged["at_node_1"] - df_merged["at_node_0"] + ).dt.total_seconds() * 1000 print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") - print("Each row represents a unique block seen by both nodes, joined by hash and slot.") + print( + "Each row represents a unique block seen by both nodes, joined by hash and slot." + ) print(df_merged.head()) print(f"\nTotal unique block events matched: {len(df_merged)}") From a4d5b2aa0024d714ba6a7b05b3876a7f0482cfb3 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 21 Oct 2025 16:36:49 +0200 Subject: [PATCH 034/119] Add Leios demo test data --- scripts/leios-demo/data/cardano-node-0.log | 2275 ++++++++++++++++++++ scripts/leios-demo/data/cardano-node-1.log | 1852 ++++++++++++++++ 2 files changed, 4127 insertions(+) create mode 100644 scripts/leios-demo/data/cardano-node-0.log create mode 100644 scripts/leios-demo/data/cardano-node-1.log diff --git a/scripts/leios-demo/data/cardano-node-0.log b/scripts/leios-demo/data/cardano-node-0.log new file mode 100644 index 0000000000..16d3701e7d --- /dev/null +++ b/scripts/leios-demo/data/cardano-node-0.log @@ -0,0 +1,2275 @@ +Resolving dependencies... +Node configuration: NodeConfiguration {ncSocketConfig = SocketConfig {ncNodeIPv4Addr = Last {getLast = Just 0.0.0.0}, ncNodeIPv6Addr = Last {getLast = Nothing}, ncNodePortNumber = Last {getLast = Just 3002}, ncSocketPath = Last {getLast = Just "node-0.socket"}}, ncConfigFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/config.json", ncTopologyFile = "topology-node-0.json", ncDatabaseFile = OnePathForAllDbs "/tmp/tmp.HodA1h2aAY/node-0/db", ncProtocolFiles = ProtocolFilepaths {byronCertFile = Nothing, byronKeyFile = Nothing, shelleyKESFile = Nothing, shelleyVRFFile = Nothing, shelleyCertFile = Nothing, shelleyBulkCredsFile = Nothing}, ncValidateDB = False, ncShutdownConfig = ShutdownConfig {scIPC = Nothing, scOnSyncLimit = Just NoShutdown}, ncStartAsNonProducingNode = False, ncProtocolConfig = NodeProtocolConfigurationCardano (NodeByronProtocolConfiguration {npcByronGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/byron/genesis.json", npcByronGenesisFileHash = Nothing, npcByronReqNetworkMagic = RequiresMagic, npcByronPbftSignatureThresh = Nothing, npcByronSupportedProtocolVersionMajor = 3, npcByronSupportedProtocolVersionMinor = 0, npcByronSupportedProtocolVersionAlt = 0}) (NodeShelleyProtocolConfiguration {npcShelleyGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis-shelley.json", npcShelleyGenesisFileHash = Nothing}) (NodeAlonzoProtocolConfiguration {npcAlonzoGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis.alonzo.json", npcAlonzoGenesisFileHash = Nothing}) (NodeConwayProtocolConfiguration {npcConwayGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis.conway.json", npcConwayGenesisFileHash = Nothing}) (NodeHardForkProtocolConfiguration {npcExperimentalHardForksEnabled = True, npcTestShelleyHardForkAtEpoch = Just (EpochNo 0), npcTestShelleyHardForkAtVersion = Nothing, npcTestAllegraHardForkAtEpoch = Just (EpochNo 0), npcTestAllegraHardForkAtVersion = Nothing, npcTestMaryHardForkAtEpoch = Just (EpochNo 0), npcTestMaryHardForkAtVersion = Nothing, npcTestAlonzoHardForkAtEpoch = Just (EpochNo 0), npcTestAlonzoHardForkAtVersion = Nothing, npcTestBabbageHardForkAtEpoch = Just (EpochNo 0), npcTestBabbageHardForkAtVersion = Nothing, npcTestConwayHardForkAtEpoch = Just (EpochNo 0), npcTestConwayHardForkAtVersion = Nothing}) (NodeCheckpointsConfiguration {npcCheckpointsFile = Nothing, npcCheckpointsFileHash = Nothing}), ncDiffusionMode = InitiatorAndResponderDiffusionMode, ncExperimentalProtocolsEnabled = True, ncMaxConcurrencyBulkSync = Nothing, ncMaxConcurrencyDeadline = Nothing, ncLoggingSwitch = True, ncLogMetrics = True, ncTraceConfig = TraceDispatcher (TraceSelection {traceVerbosity = NormalVerbosity, traceAcceptPolicy = OnOff {isOn = False}, traceBlockFetchClient = OnOff {isOn = False}, traceBlockFetchDecisions = OnOff {isOn = True}, traceBlockFetchProtocol = OnOff {isOn = False}, traceBlockFetchProtocolSerialised = OnOff {isOn = False}, traceBlockFetchServer = OnOff {isOn = False}, traceBlockchainTime = OnOff {isOn = False}, traceChainDB = OnOff {isOn = True}, traceChainSyncBlockServer = OnOff {isOn = False}, traceChainSyncClient = OnOff {isOn = True}, traceChainSyncHeaderServer = OnOff {isOn = False}, traceChainSyncProtocol = OnOff {isOn = False}, traceConnectionManager = OnOff {isOn = True}, traceConnectionManagerCounters = OnOff {isOn = True}, traceConnectionManagerTransitions = OnOff {isOn = False}, traceDebugPeerSelectionInitiatorTracer = OnOff {isOn = False}, traceDebugPeerSelectionInitiatorResponderTracer = OnOff {isOn = False}, traceDiffusionInitialization = OnOff {isOn = False}, traceDnsResolver = OnOff {isOn = False}, traceDnsSubscription = OnOff {isOn = True}, traceErrorPolicy = OnOff {isOn = True}, traceForge = OnOff {isOn = True}, traceForgeStateInfo = OnOff {isOn = True}, traceGDD = OnOff {isOn = False}, traceHandshake = OnOff {isOn = False}, traceInboundGovernor = OnOff {isOn = True}, traceInboundGovernorCounters = OnOff {isOn = True}, traceInboundGovernorTransitions = OnOff {isOn = True}, traceIpSubscription = OnOff {isOn = True}, traceKeepAliveClient = OnOff {isOn = False}, traceLedgerPeers = OnOff {isOn = False}, traceLocalChainSyncProtocol = OnOff {isOn = False}, traceLocalConnectionManager = OnOff {isOn = True}, traceLocalErrorPolicy = OnOff {isOn = True}, traceLocalHandshake = OnOff {isOn = True}, traceLocalInboundGovernor = OnOff {isOn = True}, traceLocalMux = OnOff {isOn = False}, traceLocalRootPeers = OnOff {isOn = False}, traceLocalServer = OnOff {isOn = True}, traceLocalStateQueryProtocol = OnOff {isOn = False}, traceLocalTxMonitorProtocol = OnOff {isOn = False}, traceLocalTxSubmissionProtocol = OnOff {isOn = False}, traceLocalTxSubmissionServer = OnOff {isOn = False}, traceMempool = OnOff {isOn = True}, traceBackingStore = OnOff {isOn = False}, traceMux = OnOff {isOn = True}, tracePeerSelection = OnOff {isOn = True}, tracePeerSelectionCounters = OnOff {isOn = True}, tracePeerSelectionActions = OnOff {isOn = True}, tracePublicRootPeers = OnOff {isOn = False}, traceSanityCheckIssue = OnOff {isOn = False}, traceServer = OnOff {isOn = True}, traceTxInbound = OnOff {isOn = False}, traceTxOutbound = OnOff {isOn = False}, traceTxSubmissionProtocol = OnOff {isOn = False}, traceTxSubmission2Protocol = OnOff {isOn = False}, traceKeepAliveProtocol = OnOff {isOn = False}, tracePeerSharingProtocol = OnOff {isOn = False}, traceGsm = OnOff {isOn = True}, traceCsj = OnOff {isOn = True}, traceDevotedBlockFetch = OnOff {isOn = True}}), ncTraceForwardSocket = Nothing, ncMaybeMempoolCapacityOverride = Nothing, ncLedgerDbConfig = LedgerDbConfiguration DefaultNumOfDiskSnapshots (RequestedSnapshotInterval 4230s) DefaultQueryBatchSize V2InMemory (DeprecatedOptions ["SnapshotInterval"]), ncProtocolIdleTimeout = 5s, ncTimeWaitTimeout = 60s, ncEgressPollInterval = 0s, ncChainSyncIdleTimeout = TimeoutOverride 0s, ncAcceptedConnectionsLimit = AcceptedConnectionsLimit {acceptedConnectionsHardLimit = 512, acceptedConnectionsSoftLimit = 384, acceptedConnectionsDelay = 5s}, ncDeadlineTargetOfRootPeers = 60, ncDeadlineTargetOfKnownPeers = 150, ncDeadlineTargetOfEstablishedPeers = 40, ncDeadlineTargetOfActivePeers = 15, ncDeadlineTargetOfKnownBigLedgerPeers = 15, ncDeadlineTargetOfEstablishedBigLedgerPeers = 10, ncDeadlineTargetOfActiveBigLedgerPeers = 5, ncSyncTargetOfRootPeers = 0, ncSyncTargetOfKnownPeers = 150, ncSyncTargetOfEstablishedPeers = 40, ncSyncTargetOfActivePeers = 15, ncSyncTargetOfKnownBigLedgerPeers = 100, ncSyncTargetOfEstablishedBigLedgerPeers = 40, ncSyncTargetOfActiveBigLedgerPeers = 30, ncConsensusMode = PraosMode, ncMinBigLedgerPeersForTrustedState = NumberOfBigLedgerPeers {getNumberOfBigLedgerPeers = 5}, ncEnableP2P = EnabledP2PMode, ncPeerSharing = PeerSharingDisabled, ncGenesisConfig = GenesisConfig {gcBlockFetchConfig = GenesisBlockFetchConfiguration {gbfcGracePeriod = 0s}, gcChainSyncLoPBucketConfig = ChainSyncLoPBucketDisabled, gcCSJConfig = CSJDisabled, gcLoEAndGDDConfig = LoEAndGDDDisabled, gcHistoricityCutoff = Nothing}, ncResponderCoreAffinityPolicy = NoResponderCoreAffinity} +{"at":"2025-10-20T19:55:59.489139545Z","ns":"Reflection.TracerInfo","data":{"allTracers":" BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockFetch.Server BlockchainTime ChainDB ChainDB.ReplayBlock ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised ChainSync.ServerBlock ChainSync.ServerHeader Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup Forge.Loop Forge.StateInfo Forge.Stats KeepAlive.Remote Mempool Net Net.Churn Net.ConnectionManager.Local Net.ConnectionManager.Remote Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Local Net.InboundGovernor.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.PeerSelection.Selection Net.Peers.Ledger Net.Peers.List Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxInbound TxSubmission.TxOutbound Version","kind":"TracerMeta","noMetrics":"BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockchainTime ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup KeepAlive.Remote Net Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.Ledger Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound","silentTracers":" BlockFetch.Remote.Serialised ChainDB.ReplayBlock ChainSync.Remote.Serialised ChainSync.ServerBlock ChainSync.ServerHeader Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Forge.StateInfo Forge.Stats KeepAlive.Remote Net Net.Churn Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.PeerSelection Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.Ledger Net.Peers.List PeerSharing.Remote TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound"},"sev":"Notice","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.489954019Z","ns":"Reflection.TracerConfigInfo","data":{"conf":{"TraceOptionForwarder":{"tofConnQueueSize":64,"tofDisconnQueueSize":128,"tofMaxReconnectDelay":30,"tofVerbosity":"Minimum"},"TraceOptionLedgerMetricsFrequency":null,"TraceOptionMetricsPrefix":"cardano.node.metrics.","TraceOptionNodeName":"node-0","TraceOptionPeerFrequency":2000,"TraceOptionResourceFrequency":1000,"TraceOptions":{"":{"backends":["Stdout MachineFormat","EKGBackend","Forwarder"],"detail":"DNormal","severity":"Notice"},"BlockFetch.Client":{"severity":"Debug"},"BlockFetch.Decision":{"severity":"Debug"},"BlockFetch.Remote":{"severity":"Debug"},"BlockFetch.Remote.Serialised":{"severity":"Notice"},"BlockFetch.Server":{"severity":"Notice"},"BlockchainTime":{"severity":"Notice"},"ChainDB":{"severity":"Debug"},"ChainDB.AddBlockEvent.AddBlockValidation":{"severity":"Debug"},"ChainDB.LedgerEvent.Flavor.V1.OnDisk.BackingStoreEvent":{"severity":"Silence"},"ChainDB.LedgerEvent.Forker":{"severity":"Notice"},"ChainDB.ReplayBlock.LedgerReplay":{"severity":"Notice"},"ChainSync.Client":{"severity":"Debug"},"ChainSync.Local":{"severity":"Debug"},"ChainSync.Remote":{"severity":"Debug"},"ChainSync.Remote.Serialised":{"severity":"Notice"},"ChainSync.ServerBlock":{"severity":"Notice"},"ChainSync.ServerHeader":{"severity":"Notice"},"Consensus.GSM":{"severity":"Info"},"Forge.Loop":{"severity":"Notice"},"Forge.StateInfo":{"severity":"Notice"},"LedgerMetrics":{"severity":"Info"},"Mempool":{"severity":"Notice"},"Mempool.AttemptAdd":{"severity":"Silence"},"Mempool.LedgerFound":{"severity":"Silence"},"Mempool.LedgerNotFound":{"severity":"Notice"},"Mempool.SyncNotNeeded":{"severity":"Silence"},"Mempool.Synced":{"severity":"Silence"},"Net":{"severity":"Notice"},"Net.AcceptPolicy":{"severity":"Notice"},"Net.ConnectionManager.Local":{"severity":"Notice"},"Net.ConnectionManager.Remote":{"severity":"Notice"},"Net.ConnectionManager.Remote.ConnectionManagerCounters":{"severity":"Notice"},"Net.DNSResolver":{"severity":"Notice"},"Net.ErrorPolicy":{"severity":"Info"},"Net.ErrorPolicy.Local":{"severity":"Notice"},"Net.ErrorPolicy.Remote":{"severity":"Notice"},"Net.Handshake.Local":{"severity":"Notice"},"Net.Handshake.Remote":{"severity":"Notice"},"Net.InboundGovernor":{"severity":"Warning"},"Net.InboundGovernor.Local":{"severity":"Notice"},"Net.InboundGovernor.Remote":{"severity":"Notice"},"Net.InboundGovernor.Transition":{"severity":"Notice"},"Net.Mux.Local":{"severity":"Notice"},"Net.Mux.Remote":{"severity":"Notice"},"Net.PeerSelection":{"severity":"Notice"},"Net.PeerSelection.Actions":{"severity":"Notice"},"Net.PeerSelection.Counters":{"detail":"DMinimal","severity":"Notice"},"Net.PeerSelection.Initiator":{"severity":"Notice"},"Net.PeerSelection.Responder":{"severity":"Notice"},"Net.PeerSelection.Selection":{"severity":"Notice"},"Net.Peers.Ledger":{"severity":"Notice"},"Net.Peers.List":{"severity":"Notice"},"Net.Peers.LocalRoot":{"severity":"Notice"},"Net.Peers.PublicRoot":{"severity":"Notice"},"Net.Server.Local":{"severity":"Notice"},"Net.Server.Remote":{"severity":"Notice"},"Net.Subscription.DNS":{"severity":"Notice"},"Net.Subscription.IP":{"severity":"Notice"},"NodeState":{"severity":"Notice"},"Resources":{"severity":"Notice"},"Shutdown":{"severity":"Notice"},"Startup":{"severity":"Notice"},"Startup.DiffusionInit":{"severity":"Notice"},"StateQueryServer":{"severity":"Notice"},"TxSubmission.Local":{"severity":"Notice"},"TxSubmission.LocalServer":{"severity":"Notice"},"TxSubmission.MonitorClient":{"severity":"Notice"},"TxSubmission.Remote":{"severity":"Notice"},"TxSubmission.TxInbound":{"severity":"Notice"},"TxSubmission.TxOutbound":{"severity":"Notice"},"Version.NodeVersion":{"severity":"Info"}}}},"sev":"Notice","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.489970643Z","ns":"Version.NodeVersion","data":{"applicationName":"cardano-node","applicationVersion":"10.5.1","architecture":"x86_64","compilerName":"ghc","compilerVersion":"9.6.7","gitRevision":"ca1ec278070baf4481564a6ba7b4a5b9e3d9f366","osName":"linux"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.493601066Z","ns":"Startup.MovedTopLevelOption","data":{"kind":"MovedTopLevelOption","option":"SnapshotInterval"},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.49612176Z","ns":"ChainDB.LastShutdownUnclean","data":{"kind":"LastShutdownUnclean"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.496187541Z","ns":"ChainDB.OpenEvent.StartedOpeningDB","data":{"kind":"StartedOpeningDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.496198335Z","ns":"ChainDB.OpenEvent.StartedOpeningImmutableDB","data":{"kind":"StartedOpeningImmutableDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.496449571Z","ns":"ChainDB.ImmDbEvent.NoValidLastLocation","data":{"kind":"NoValidLastLocation"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.49660891Z","ns":"ChainDB.OpenEvent.OpenedImmutableDB","data":{"epoch":"0","immtip":{"kind":"GenesisPoint"},"kind":"OpenedImmutableDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.4966248Z","ns":"ChainDB.OpenEvent.StartedOpeningVolatileDB","data":{"kind":"StartedOpeningVolatileDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.496749503Z","ns":"ChainDB.OpenEvent.OpenedVolatileDB","data":{"kind":"OpenedVolatileDB","maxSlotNo":"NoMaxSlotNo"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.496764035Z","ns":"ChainDB.OpenEvent.StartedOpeningLgrDB","data":{"kind":"StartedOpeningLgrDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.49680469Z","ns":"ChainDB.LedgerEvent.Replay.ReplayStart.ReplayFromGenesis","data":{"kind":"ReplayFromGenesis"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497489633Z","ns":"ChainDB.OpenEvent.OpenedLgrDB","data":{"kind":"OpenedLgrDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497511285Z","ns":"ChainDB.InitChainSelEvent.StartedInitChainSelection","data":{"kind":"Follower.StartedInitChainSelection"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497579652Z","ns":"ChainDB.InitChainSelEvent.InitialChainSelected","data":{"kind":"Follower.InitialChainSelected"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497661878Z","ns":"ChainDB.OpenEvent.OpenedDB","data":{"immtip":{"kind":"GenesisPoint"},"kind":"OpenedDB","tip":{"kind":"GenesisPoint"}},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497714704Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.497936136Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:55:59.497907201 UTC"},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498313973Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498385323Z","ns":"Shutdown.ArmedAt","data":{"kind":"ShutdownArmedAt","limit":{"tag":"NoShutdown"}},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498615021Z","ns":"Net.Server.Local.Started","data":{"addresses":[{"path":"node-0.socket"}],"kind":"AcceptPolicyTrace"},"sev":"Notice","thread":"37","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498645045Z","ns":"Net.Server.Remote.Started","data":{"addresses":[{"addr":"0.0.0.0","port":"3002"}],"kind":"AcceptPolicyTrace"},"sev":"Notice","thread":"36","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498831905Z","ns":"Net.PeerSelection.Selection.UseBootstrapPeersChanged","data":{"kind":"UseBootstrapPeersChanged","useBootstrapPeers":[]},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498947738Z","ns":"Consensus.GSM.GsmEventPreSyncingToSyncing","data":{"kind":"GsmEventPreSyncingToSyncing"},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.498975974Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":0},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":0,"targetActivePeers":0,"targetEstablishedBigLedgerPeers":0,"targetEstablishedPeers":0,"targetKnownBigLedgerPeers":0,"targetKnownPeers":0,"targetRootPeers":0}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.499074003Z","ns":"Net.PeerSelection.Selection.LocalRootPeersChanged","data":{"current":{"groups":[[1,1,[[{"address":"127.0.0.1","port":"3001"},{"diffusionMode":"InitiatorAndResponderDiffusionMode","extraFlags":"IsTrustable","peerAdvertise":false}]]]],"kind":"LocalRootPeers"},"kind":"LocalRootPeersChanged","previous":{"groups":[],"kind":"LocalRootPeers"}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50126577Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502376114Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50239225Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502420328Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502436871Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502467689Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502490603Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502516002Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50253496Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502553561Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502569131Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50259115Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502610673Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502625303Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502646222Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502667356Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502681991Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502699049Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502715211Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502731255Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502754309Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502779414Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502794165Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502816252Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50283422Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502848768Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50286955Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502890964Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502905205Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502922722Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502940788Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502956953Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502979536Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.502997308Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503011234Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503033023Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503050824Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503065163Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503086123Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503106373Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503120593Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503137846Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503154031Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503169663Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503192166Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503208212Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503223966Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503244887Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503263685Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50327793Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50340166Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.503468568Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505356889Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505476157Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"kind":"GenesisPoint"}},"sev":"Notice","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505500556Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505512567Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505512898Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505540759Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505555209Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","blockNo":0,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":2},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505564654Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505603075Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505636784Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505670661Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505704485Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50573201Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.5057627Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505793005Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505819653Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505848245Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505877012Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505904519Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505932532Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.505961698Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506001392Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506608088Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506674091Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":false},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506712539Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506731499Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.506758273Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","blockNo":1,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":44},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507307137Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507353863Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507401173Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507434576Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507465219Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507492904Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507522088Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507551085Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507593401Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507622411Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50765078Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507675856Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50769484Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507703513Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507731418Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507755378Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507795778Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507822163Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507833602Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.507850214Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","blockNo":2,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":52},"sev":"Info","thread":"68","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.489139545 UTC to 2025-10-20 19:55:59.508536524 UTC +{"at":"2025-10-20T19:55:59.508495451Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.508536524Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":1,"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.508551255Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50873154Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.508749481Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","blockNo":3,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":53},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.508926236Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.508978608Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50901236Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509041123Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509071399Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509100993Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509415542Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509442631Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["4e93dab@2","bd384ce@44","23b021f@52"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509460069Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":2,"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509474338Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509482779Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50949471Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","blockNo":4,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":59},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509683457Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50975607Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509796767Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509830337Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509862822Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509890666Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509919471Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.509947641Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.50997457Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510001741Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510042676Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510062284Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510102106Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":3,"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510114974Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510123317Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510137007Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","blockNo":5,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":77},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510719534Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51075604Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":4,"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510768475Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510776699Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.510789137Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","blockNo":6,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":80},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511321898Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511347308Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"SendFetchRequest","length":3,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511373793Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51139433Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511410899Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":5,"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511423844Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.511432103Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51144361Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","blockNo":7,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":95},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512016276Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512058494Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":6,"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512070999Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51207951Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512091099Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","blockNo":8,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":108},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512671314Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512710985Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":7,"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51272305Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51273082Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.512742224Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","blockNo":9,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":111},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513181951Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513197388Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513313685Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513349725Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":8,"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513362485Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513376012Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513388084Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","blockNo":10,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":148},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.513899159Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","blockSize":1033,"kind":"MsgBlock","txIds":["c3b5fef45f23b1ae942b9386e42f70a3c83aab8ef8fe95054c3f27cfb3cd32a6"]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51404274Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514081592Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514139609Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","delay":1037543.513919911,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":1033},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514242173Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514317781Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514351227Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514404096Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","delay":1037501.514250285,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514474252Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514542854Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514571332Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514610835Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","delay":1037493.514481027,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514646667Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514660978Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514720906Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514767077Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":9,"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514780744Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514788702Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.514800478Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","blockNo":11,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":162},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515072066Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515096528Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515128394Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"blockNo":"0","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515641773Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515710017Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":10,"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515722141Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51573086Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.515743577Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","blockNo":12,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":179},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516183857Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"blockNo":"0","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516292597Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"kind":"GenesisPoint"}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516330072Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516398088Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516418772Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516454649Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516491253Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":11,"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516503655Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516512071Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51652396Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","blockNo":13,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":183},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51656459Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":183},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.516658642Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","targetBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.5179547Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51799496Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518067436Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":0,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":2,"tieBreakVRF":"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf"},"newtip":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2"},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518148097Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518213085Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518228693Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518259717Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"blockNo":"1","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518344862Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"blockNo":"1","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518424377Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518448785Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518496895Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.518504656Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.51870582Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","targetBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.519565106Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.519598471Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.519689004Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":1,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":44,"tieBreakVRF":"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951"},"newtip":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","oldTipSelectView":{"chainLength":0,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":2,"tieBreakVRF":"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.521953743Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522026683Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522040048Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.508551255 UTC to 2025-10-20 19:55:59.522808468 UTC +{"at":"2025-10-20T19:55:59.522062584Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"blockNo":"2","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522132106Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"blockNo":"2","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522184646Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522205609Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522219526Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["5ecd12b@53","0341e87@59","312446d@77","b69dee5@80","f0c284a@95","b986a90@108","8a9fdda@111","b0c2dd7@148","5fc55ce@162","a1ad392@179"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522242543Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522250167Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522381519Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":183},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.522808468Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52287015Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","targetBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523355865Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523389831Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"SendFetchRequest","length":10,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52341623Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523464152Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523520563Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":12,"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523538469Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523547362Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.523563504Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","blockNo":14,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":187},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.524574546Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.524628608Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":13,"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.524643279Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.524651464Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.524663745Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","blockNo":15,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":188},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525275473Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525332248Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525465583Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":2,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":52,"tieBreakVRF":"a7ebd222c942746c013165f0adc2abfec5f1d25f7b41b2aef928ab4c865f1b48775a18e1699e447b118e89591d663968990ef90f7807b5b2a4295561b0264d69"},"newtip":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","oldTipSelectView":{"chainLength":1,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":44,"tieBreakVRF":"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525584348Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525663639Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525683284Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525757089Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525816552Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":14,"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525829451Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525837975Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.525853749Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","blockNo":16,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":222},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52640094Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526416562Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526480496Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526533533Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526537325Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526552579Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526583099Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","delay":1037492.526485912,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526590794Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":15,"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526604094Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526612329Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526624772Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","blockNo":17,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":247},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526632046Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526666067Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526676289Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":247},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526681138Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526700764Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","delay":1037486.526638026,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526723243Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526736891Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526737227Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526759667Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"blockNo":"3","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526767786Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526781922Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526800759Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","delay":1037468.526740655,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526832955Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"blockNo":"3","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526836745Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526866524Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526880343Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526885115Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526898023Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","delay":1037465.526840291,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526906543Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526934381Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526936591Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526943783Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52696508Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526978662Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526981489Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","targetBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.526995923Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","delay":1037450.526938302,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527030711Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527059981Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52707386Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527091513Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","delay":1037437.527033868,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527126971Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527156853Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527170403Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527187793Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","delay":1037434.527130271,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527222092Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527251315Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527265691Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527283582Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","delay":1037397.527225328,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527319154Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527348376Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527361758Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"AddedBlockToQueue","queueSize":8},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527390676Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","delay":1037383.527322391,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527427305Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52745795Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527472043Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"AddedBlockToQueue","queueSize":9},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527489446Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","delay":1037366.527431142,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527508535Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527517288Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527937833Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.527965383Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528074532Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528128489Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528140183Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528181204Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"blockNo":"4","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528249245Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"blockNo":"4","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528311901Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2},"head":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.52833098Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528359968Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528374834Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528810045Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.528833325Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":2}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.529602271Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","targetBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531139627Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531186725Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531343101Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531431194Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531452463Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531524846Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"blockNo":"5","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53162391Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"blockNo":"5","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531723751Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44},"head":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531755552Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.531803427Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53181893Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.532119094Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","targetBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.532874319Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53289821Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":44}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533102604Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["56515bf@183","60fd8fc@187","48cf5b4@188","0a723e7@222"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533442561Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533542517Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533582235Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.52287015 UTC to 2025-10-20 19:55:59.53412163 UTC +{"at":"2025-10-20T19:55:59.533706349Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533717752Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533737051Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533761033Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533771613Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533789751Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533844855Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"blockNo":"6","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.533939815Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"blockNo":"6","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534031456Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52},"head":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534062654Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534106842Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53412163Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534421207Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534572771Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":52}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534630313Z","ns":"ChainDB.LedgerEvent.Snapshot.TookSnapshot","data":{"enclosedTime":{"tag":"RisingEdge"},"kind":"TookSnapshot","snapshot":{"kind":"snapshot"},"tip":"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8"},"sev":"Info","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.534664157Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":247},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.535259413Z","ns":"ChainDB.LedgerEvent.Snapshot.TookSnapshot","data":{"enclosedTime":{"contents":6.24381e-4,"tag":"FallingEdgeWith"},"kind":"TookSnapshot","snapshot":{"kind":"snapshot"},"tip":"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8"},"sev":"Info","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.535384249Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","targetBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.535941701Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536016959Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":16,"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536042158Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536057226Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536084126Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","blockNo":18,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":280},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536169217Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":280},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536376811Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536406759Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536512484Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536570116Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536583191Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536619432Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"blockNo":"7","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536687609Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"blockNo":"7","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536749535Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53},"head":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536767249Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536800015Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.536807509Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537028328Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","targetBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537202207Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537222902Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":53}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537863626Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537890548Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537889787Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537903919Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537953697Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.537981341Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53800275Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538022935Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538031471Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538042423Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538053489Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","delay":1037362.537960077,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538076267Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"blockNo":"8","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538098678Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538131332Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538136123Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"blockNo":"8","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538146455Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538166527Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","delay":1037358.538103146,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538194809Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59},"head":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538203292Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538212699Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538233745Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538241739Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538247954Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538249435Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538266434Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","delay":1037357.538206879,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538308908Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538339356Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538353467Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"AddedBlockToQueue","queueSize":8},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538384602Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","delay":1037323.53831234,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538405933Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53841401Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.538474026Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","targetBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539271088Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539295729Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539389091Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539437154Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539447588Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539496626Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"blockNo":"9","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539569438Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"blockNo":"9","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539644935Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77},"head":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.53966278Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539692407Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539699836Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.539893464Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":280},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.540314496Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","targetBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541218129Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.54130194Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":17,"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541306442Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541322709Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541334122Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541351345Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","blockNo":19,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":304},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541505891Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":304},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.541911372Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.54194662Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542061478Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542121765Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542136305Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542197063Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"blockNo":"10","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542278778Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"blockNo":"10","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542380885Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80},"head":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542401258Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542434715Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542441971Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.542746501Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","targetBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.543098423Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.543127595Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":77}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550596127Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550619288Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":80}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55066887Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["85d81d9@247","af465fe@280"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550677247Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550711884Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550818584Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550878385Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55089018Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550931374Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"blockNo":"11","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.550937281Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551007993Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"blockNo":"11","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551077067Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95},"head":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551097437Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551131795Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551139727Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551470967Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":304},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.551915128Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","targetBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552295204Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552327172Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"SendFetchRequest","length":2,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552355979Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55252606Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552549175Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":95}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55262516Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552724174Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":18,"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552746794Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552757832Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.552775167Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","blockNo":20,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":325},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553354449Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553396511Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.534421207 UTC to 2025-10-20 19:55:59.553783062 UTC +{"at":"2025-10-20T19:55:59.553510695Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553572391Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553584074Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553623818Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"blockNo":"12","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553694621Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"blockNo":"12","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553762678Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108},"head":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553783062Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553890253Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553911881Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":108}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553819402Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.553966909Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.554066256Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.554165502Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":19,"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.554186593Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.554196891Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55421264Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","blockNo":21,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":333},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.554924804Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","targetBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555570895Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555596864Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55565744Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55567927Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555755532Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":20,"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555755798Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555777245Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555788245Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555792873Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555804308Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","blockNo":22,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":351},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55584031Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","delay":1037298.555687484,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":862},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55588301Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":351},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555907747Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.555959841Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55598613Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556023754Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","delay":1037265.55591486,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556059363Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556073371Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556234377Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55626877Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556395759Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556455387Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556468264Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556512065Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"blockNo":"13","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556586986Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"blockNo":"13","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556656412Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111},"head":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556676671Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556709858Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556716894Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.556937321Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":351},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.557385155Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","targetBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.557725213Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.557748513Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":111}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558056112Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558159515Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":21,"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558183637Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558195209Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558212843Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","blockNo":23,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":357},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.558974953Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559020791Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559154503Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559211428Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.55927077Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":22,"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559286005Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559295564Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559309597Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","blockNo":24,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":362},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559822101Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.559843171Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":148}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560011546Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560034786Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560071452Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"blockNo":"14","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56014619Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560201132Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":23,"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560215127Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560223436Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56023577Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","blockNo":25,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":376},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56028553Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":376},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560452489Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"blockNo":"14","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560524817Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148},"head":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560556709Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560594278Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560601986Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.560644365Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","targetBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561443312Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["05f2b94@304","a55ea78@325","81087aa@333","e8cc9be@351","82758a7@357","9769d5e@362"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561520739Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561547459Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561650983Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561706507Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561718828Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561753273Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"blockNo":"15","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561821803Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"blockNo":"15","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561861732Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561882769Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162},"head":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561900719Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561930589Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.561937542Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.562228529Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","targetBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563074735Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563096873Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"SendFetchRequest","length":6,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563107616Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563122243Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563133858Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563233599Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563290842Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563290924Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563302552Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563314699Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":162}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563338158Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"blockNo":"16","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563577858Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"blockNo":"16","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563643119Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179},"head":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563662861Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563699487Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563707628Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.563743154Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","targetBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564560467Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564591624Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564685702Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564710131Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564730384Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":179}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564740212Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564752065Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564789789Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"blockNo":"17","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564852944Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"blockNo":"17","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56491567Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183},"head":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.564934651Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56496664Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56497393Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.565147844Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.565163718Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":183}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.565290898Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":376},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.565742082Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","targetBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.566420309Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.566502805Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":24,"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.566524672Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.566535739Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.566552419Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","blockNo":26,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":392},"sev":"Info","thread":"68","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.553819402 UTC to 2025-10-20 19:55:59.567261876 UTC +{"at":"2025-10-20T19:55:59.567228925Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567261876Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567381112Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567263261Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567431378Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56744034Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567452472Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567489074Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"blockNo":"18","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567512054Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567569999Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"blockNo":"18","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567585431Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567619318Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567635074Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187},"head":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567653205Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567664849Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","delay":1037241.567521234,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567686762Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567694239Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567734195Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56776472Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567787753Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567814666Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567845736Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":25,"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567848066Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","delay":1037220.567741731,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567867677Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567878444Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567895101Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","blockNo":27,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":397},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567914615Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567965352Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.567991304Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568024778Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","delay":1037212.567921142,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568083298Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568132952Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568158767Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568190568Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","delay":1037194.568089331,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568248119Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568297247Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568322738Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568353967Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","delay":1037188.568254413,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":863},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56842179Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568471048Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568496303Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568528222Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","delay":1037183.568428071,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568550845Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","targetBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.568561105Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.56857579Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569131156Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569181196Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":26,"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569196907Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569206317Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569219944Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","blockNo":28,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":444},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569289807Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":444},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569505189Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569533009Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569636024Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569693479Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569707698Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569760489Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"blockNo":"19","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569830059Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"blockNo":"19","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569909299Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188},"head":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569928099Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569962028Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.569969657Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.570163139Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":444},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.570576819Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","targetBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572056093Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572088969Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572198993Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572258335Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572271546Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572341741Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"blockNo":"20","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572429233Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"blockNo":"20","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572519207Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222},"head":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572537126Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572571169Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.57257869Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572671962Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572783006Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572869127Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":27,"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572890589Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572901172Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572917896Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","blockNo":29,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":487},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.572967161Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.573288369Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":487},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.573394962Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.573415392Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":222}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.573418669Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","targetBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574428198Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["a98a7f6@376","b7c2df0@392","521f832@397","12ab6ce@444"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574494899Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574526699Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574630454Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574687807Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574699654Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574736611Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"blockNo":"21","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574766229Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574806477Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"blockNo":"21","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574870138Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247},"head":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574888403Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574921562Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.574929396Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.575174334Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":487},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.57569928Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","targetBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.575954902Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.575985489Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.5760109Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576166618Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576190247Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":247}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576346141Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576445253Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":28,"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576466735Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576477051Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.576493757Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","blockNo":30,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":505},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577157294Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577210011Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":29,"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577225573Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577234472Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577247448Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","blockNo":31,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":558},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577299757Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":558},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577598375Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577637793Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.577746567Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578004147Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578017783Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578053474Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"blockNo":"22","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.57812261Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"blockNo":"22","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578187348Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280},"head":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578205432Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578235414Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578242504Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.578279945Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","targetBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.567263261 UTC to 2025-10-20 19:55:59.579136528 UTC +{"at":"2025-10-20T19:55:59.579136528Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.57916356Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579417515Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579473402Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579472541Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579485177Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579506444Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":280}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579520532Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"blockNo":"23","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579589651Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"blockNo":"23","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579650149Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304},"head":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579667598Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579698126Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.579705737Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580042149Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","targetBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580728237Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580755862Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":304}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580805725Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58082401Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580881822Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580943476Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.580974046Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581018005Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","delay":1037169.580889759,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58108731Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581140369Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581167901Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581201872Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","delay":1037153.581095006,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581238468Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581261617Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58127074Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581312254Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581339474Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581384419Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","delay":1037148.58126866,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581392656Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581445188Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581451876Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581464482Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581496851Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581501215Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"blockNo":"24","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581524987Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581558717Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","delay":1037101.581452331,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581574413Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"blockNo":"24","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581592617Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581608235Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581639243Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325},"head":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581657071Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581690312Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.581697185Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.582147754Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","targetBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.582617717Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58264089Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":325}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583014217Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583040574Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583138039Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58318797Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583200418Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583234682Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"blockNo":"25","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583301438Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"blockNo":"25","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583360472Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333},"head":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583389184Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583813421Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.583824674Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58386518Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","targetBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584668365Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58469337Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584789214Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584837927Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584849025Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584899067Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"blockNo":"26","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.584961483Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"blockNo":"26","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585035419Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351},"head":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585053392Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585083534Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585090775Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585570293Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585599975Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":333}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.585650982Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","targetBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586111988Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586136558Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":351}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586200638Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["2720251@487","0206ad8@505"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586561714Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586587191Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586585811Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586680568Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586728457Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586739803Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586774126Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"blockNo":"27","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586837839Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"blockNo":"27","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586897005Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357},"head":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586914341Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586945259Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.586953104Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587242368Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":558},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587671147Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587707954Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"SendFetchRequest","length":2,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587733757Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587950631Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.587999395Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":30,"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588018389Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588027558Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58804321Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","blockNo":32,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":580},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588115285Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":580},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588202218Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","targetBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588483882Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.588507788Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":357}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589002063Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589026914Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589129634Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589179649Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589189865Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589223293Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"blockNo":"28","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589298745Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"blockNo":"28","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589357982Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362},"head":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.58938444Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589414672Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589422027Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.589835052Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","targetBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.57916356 UTC to 2025-10-20 19:55:59.590751205 UTC +{"at":"2025-10-20T19:55:59.590462809Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590488671Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":362}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.59052445Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590536858Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590579368Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590621484Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590633539Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590639209Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590659291Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590669005Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","delay":1037058.590584141,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590714228Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.5907483Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590751205Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590798455Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590810538Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590844846Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"blockNo":"29","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590763795Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590904227Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","delay":1037040.590718454,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590906045Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"blockNo":"29","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590927866Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590937801Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590964799Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376},"head":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.590982252Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591011261Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591018576Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591197855Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":580},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591776113Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591792937Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":376}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.591948853Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.592003393Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":31,"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.592022349Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.592032169Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.592047252Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","blockNo":33,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":581},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.59257549Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","targetBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593122113Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593171245Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":32,"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593184782Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593192979Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593205197Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","blockNo":34,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":588},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593805068Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593844667Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.593954577Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594015969Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594028329Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594064872Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"blockNo":"30","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594136745Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"blockNo":"30","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594202403Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392},"head":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.59422044Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594254188Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594261963Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594293927Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594337539Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":33,"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594350143Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594358482Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594374218Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","blockNo":35,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":602},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594497301Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.594521645Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":392}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595773116Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595823157Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":34,"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595838228Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595847125Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595861724Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","blockNo":36,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":707},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.595913523Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":707},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.596000812Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","targetBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.596815578Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.596843985Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.596940134Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.596993513Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.597006069Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.597421057Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.597437439Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":397}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.597614319Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["6a17145@558","ef8f495@580","a1bd89b@581","d83ade2@588","a832dca@602"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.597971715Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.598022241Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.598038945Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"SendFetchRequest","length":5,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.598063274Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599235671Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599248407Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599306Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599357303Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599385362Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599413266Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","delay":1036987.599310256,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599458726Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599491817Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599506146Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599525417Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","delay":1036965.599462913,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599562028Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599592253Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599605998Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.59962405Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","delay":1036964.599565348,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599936146Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599956816Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599961542Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.599982622Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"blockNo":"31","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600046344Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600054093Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"blockNo":"31","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600083408Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600493762Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397},"head":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600512546Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","delay":1036957.599973082,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600518441Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600553129Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600560424Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60060938Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600664356Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600684146Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600707245Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","delay":1036943.600616232,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600730599Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600739852Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.600992611Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","targetBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60186336Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.601892143Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.601995025Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602049709Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602061325Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602096457Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"blockNo":"32","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602161844Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"blockNo":"32","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602223753Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444},"head":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602242331Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602273186Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60228063Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602469921Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":707},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602858971Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.602875844Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":444}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.603231765Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.603285962Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":35,"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60330511Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.603314384Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.603329447Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","blockNo":37,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":710},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.603440627Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","targetBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60443087Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604458593Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604552848Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.590763795 UTC to 2025-10-20 19:55:59.604968497 UTC +{"at":"2025-10-20T19:55:59.604604419Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604614704Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604650438Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"blockNo":"33","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604719891Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"blockNo":"33","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604780901Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487},"head":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604799092Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604831719Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604839216Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.604968497Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605077072Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605093093Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":487}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605048676Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":36,"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605232318Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605246076Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.605264144Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","blockNo":38,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":728},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606056485Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","targetBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606632773Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606720271Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":37,"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606744493Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606755393Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.606772285Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","blockNo":39,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":740},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60746239Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607499615Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607608357Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607815604Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607895634Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":38,"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607918599Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607929516Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607945807Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","blockNo":40,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":746},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.607993986Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608020438Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":505}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608768458Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["435973c@707","0dccbe6@710","e4e8468@728","120f49d@740"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608796351Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608820448Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608852972Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"blockNo":"34","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608936284Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"blockNo":"34","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.608992585Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505},"head":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609013507Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609048653Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609056157Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609098204Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609098707Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609149973Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":39,"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609165919Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609174901Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609188757Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","blockNo":41,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":756},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60958777Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609603918Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.609625886Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.60998026Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61002505Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":40,"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610038018Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610045955Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610056849Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","blockNo":42,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":780},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610103646Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":780},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610191557Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","targetBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610960085Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.610989098Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611081881Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611135361Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611146537Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611179663Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"blockNo":"35","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611245428Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"blockNo":"35","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611304509Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558},"head":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611321412Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611351176Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611358338Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.611761362Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","targetBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612453349Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612478454Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":558}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612707105Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612721538Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612781557Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612816278Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612831531Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612842024Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61285086Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612882187Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","delay":1036838.612786906,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612926016Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"events":[{"epochNo":"EpochNo 2","kind":"ShelleyUpdatedProtocolUpdates","updates":"SNothing"}],"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":35,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":602,"tieBreakVRF":"713fe8793dfe40bb9ba9315f6f1aca910bd7c9fdf8e74adc2b02494d9c37b6bc387ff810fc425fa6c26142dd07b1fc09c5ff17814bcda5532a1835f66fe260cc"},"newtip":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","oldTipSelectView":{"chainLength":34,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":588,"tieBreakVRF":"2c378d8710efaab90d72652d042886ef8d1d4b1365d016c30267cebd038f2a77c1b6bcb7fd121ad12840541641b1f4c3ca21985b8847eebceb927c82be65018d"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612927303Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61296107Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612975595Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.612995353Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","delay":1036835.612932006,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61300439Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613031556Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613055129Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613061916Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613067031Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613075741Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613094637Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","delay":1036817.613034803,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613102872Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"blockNo":"36","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613128952Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613158983Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613169972Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"blockNo":"36","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613172824Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613191307Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","delay":1036805.613132364,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613210081Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613217978Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613229809Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580},"head":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613247052Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613277712Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613284828Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.613461669Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":780},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614205132Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614254372Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":41,"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614273328Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614282752Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614297867Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","blockNo":43,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":795},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614375781Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":795},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.614464615Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","targetBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615263169Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615288427Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615387648Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615438046Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615448488Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615499398Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615502133Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"blockNo":"37","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61558582Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"blockNo":"37","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.615756879Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slotNo":795},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.616328266Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.616384614Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":42,"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61640201Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.616411181Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.616425Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","blockNo":44,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":809},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.616703441Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":580}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61702419Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617067671Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":43,"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.605048676 UTC to 2025-10-20 19:55:59.617940996 UTC +{"at":"2025-10-20T19:55:59.617080978Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.6170889Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61709995Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","blockNo":45,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":810},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617493954Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617590927Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581},"head":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617637295Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":581}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617653995Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617885291Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617928087Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":44,"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617940996Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.617949191Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.618103234Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","blockNo":46,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":829},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.618595741Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.618621537Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.618677376Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","targetBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.61921851Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619267198Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":45,"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619282078Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619291081Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619345378Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619359991Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619579236Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619609849Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619713616Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619770729Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619783647Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619820357Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"blockNo":"38","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.6198984Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"blockNo":"38","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.6199623Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588},"head":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.619980769Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.620011946Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.620019477Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.620811933Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","targetBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.621329543Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.621364784Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":588}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62150215Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["0e7f6e6@746","adc0a33@756","751da61@780","0e45f81@795","d4b3efb@809","de8f9b6@810","4135510@829"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.621960543Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622168502Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622194399Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622293059Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62234356Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62235481Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622400318Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"blockNo":"39","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62246826Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"blockNo":"39","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622529244Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602},"head":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622547734Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622579815Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.622587813Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.623150261Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","targetBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.623180724Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.623196613Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"SendFetchRequest","length":7,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.623215996Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.623980055Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624012846Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624021564Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"67","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624043341Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624144537Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624196675Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624209992Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624252014Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624364977Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.624404349Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":602}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.625469532Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.625541267Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":46,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62556123Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62557068Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.625586222Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626189829Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626222442Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":707}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626255719Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62626788Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626286372Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626300161Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626314364Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626322928Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626347919Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"68","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626350358Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62642664Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626459151Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626503521Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","delay":1036799.626358324,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626534492Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626558447Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626574532Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626598584Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"blockNo":"40","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626627451Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626654762Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626689767Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","delay":1036789.626582171,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626689825Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"blockNo":"40","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626751114Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62676407Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707},"head":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626799337Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626801817Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626829067Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626852089Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626863321Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","delay":1036765.626758085,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626868069Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626922194Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626925584Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","targetBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.617949191 UTC to 2025-10-20 19:55:59.630223461 UTC +{"at":"2025-10-20T19:55:59.626971925Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.626998147Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627031449Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","delay":1036750.626928828,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627088678Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627137786Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627163446Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627195935Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","delay":1036736.627095415,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627253425Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627301707Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627327297Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627358959Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","delay":1036735.627259454,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627427219Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627477341Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627504568Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627537619Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","delay":1036716.627433643,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"size":864},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627571142Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.627585152Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"62","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628296295Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628326143Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628440918Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62849975Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62851332Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628550777Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"blockNo":"41","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628617034Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"blockNo":"41","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628681074Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710},"head":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628699122Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628733096Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.628740842Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.629002408Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","targetBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.629688612Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62971556Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":710}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62983719Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.62986287Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.629956398Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630005261Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630016299Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630051362Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"blockNo":"42","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630147249Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"blockNo":"42","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630206018Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728},"head":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630223461Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630253956Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630401428Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630682958Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","targetBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.630992252Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631011606Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":728}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631512195Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631538253Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631634459Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631684309Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.63169558Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631730193Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"blockNo":"43","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.6317931Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"blockNo":"43","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631850762Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740},"head":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631867884Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631898224Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.631905568Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.632173197Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","targetBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.632704421Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["0d0e583@863","10f2559@887"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.632832825Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.632991025Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633153352Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633178581Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633346293Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633404233Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633415554Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633465894Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"blockNo":"44","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.63352862Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"blockNo":"44","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.6336028Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746},"head":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633620665Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633651882Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633658972Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.633897446Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","targetBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634050032Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634314629Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634330875Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":746}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634700814Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634724875Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"BlockPoint","slot":809},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634815753Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.63486276Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634873571Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634907325Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"blockNo":"45","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.634965687Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"blockNo":"45","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635024453Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756},"head":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"BlockPoint","slot":809}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635042214Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635071381Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635076599Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635078898Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635092633Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"SendFetchRequest","length":2,"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.63511677Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"63","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.635305585Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","targetBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636099142Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636124497Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"BlockPoint","slot":810},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636214091Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636259835Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636270817Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636318599Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"blockNo":"46","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636387607Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"blockNo":"46","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636458283Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780},"head":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"BlockPoint","slot":810}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636495226Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636526028Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636533367Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.636766783Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","targetBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.637563383Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.637588906Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.637678906Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.637726342Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.63773884Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.638185678Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.638216966Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":756}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.638946916Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.639397799Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.639435107Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":795}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.639757548Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",13.694856888782]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.64362682Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:02.499729248Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":0}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499438378Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500839747Z","ns":"ChainDB.FollowerEvent.FollowerNoLongerInMem","data":{"kind":"FollowerNoLongerInMem"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500911264Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500932195Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50096465Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501050598Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501203921Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501241804Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501494752Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501529024Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501636983Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501667168Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501824382Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501857019Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50192319Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501952847Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502060096Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502091862Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50223181Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502263213Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502327545Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502355528Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502430397Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502459118Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502522179Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502549543Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502657926Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502687493Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502837527Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502867406Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502968109Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.502997203Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50310504Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503135265Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50321683Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"15","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503230979Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503258627Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503361675Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"17","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503382065Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503410497Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503485308Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503511886Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503671473Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503702829Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503768203Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"21","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50378013Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"22","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.630253956 UTC to 2025-10-20 19:56:04.505598978 UTC +{"at":"2025-10-20T19:56:04.503789709Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503814534Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503936038Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503965701Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504130338Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504161943Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505598978Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50566246Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506223507Z","ns":"ChainDB.FollowerEvent.FollowerSwitchToMem","data":{"kind":"FollowerSwitchToMem"},"sev":"Debug","thread":"81","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511632212Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 2) 4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 80) b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511682641Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511699308Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511721643Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511731731Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511791383Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511875848Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511904841Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512049277Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512078735Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52157733Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 95) f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 179) a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52161755Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521632393Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521651742Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521661611Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521718685Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521857938Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521887956Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521936096Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521963266Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.536983893Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 183) 56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 222) 0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53704961Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537068997Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537098352Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537109374Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537186095Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537361186Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53740397Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546743932Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 247) 85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 247) 85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546808007Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546825739Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546850339Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546860779Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546928074Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56331864Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 280) af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 280) af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.563409678Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.563430283Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.563461385Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.563472444Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.563559856Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.579724362Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 304) 05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 333) 81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.579794863Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.579815494Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.579846549Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57985883Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.579940278Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580090456Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580126321Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584469174Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 351) e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 362) 9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584527088Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584545014Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584569915Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584581248Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584657285Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584795053Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584829382Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602185223Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 376) a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 444) 12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602250982Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602270573Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602297967Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60230954Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602405374Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602509267Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602544068Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602650977Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602681041Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609479184Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 487) 2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 505) 0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609551002Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609577648Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609611043Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609627788Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609718989Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62521803Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 558) 6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 580) ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625292626Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625322092Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625362363Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625393907Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625481827Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625609768Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625660804Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633679359Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 581) a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 707) 435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633742533Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633770505Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633804922Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633821364Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.63389964Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634065482Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634113132Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634192221Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"21","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634212843Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"22","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634228002Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634264028Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647276452Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 710) 0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 756) adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647332205Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647349828Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647387171Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647398747Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647466869Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647555066Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647586456Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647711737Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647741414Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661017213Z","ns":"ChainDB.IteratorEvent.StreamFromVolatileDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 780) 751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98)","kind":"StreamFromVolatileDB","point":"[\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795\",\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809\",\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810\",\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829\"]","to":"StreamToInclusive (RealPoint (SlotNo 829) 41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553)"},"sev":"Debug","thread":"84","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.644543859Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.644659814Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646302348Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646333851Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646435445Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646454682Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646488217Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646507531Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.646831492Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.647954106Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"101","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.648074722Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"101","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.648122336Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.648207065Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.648219278Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.648237654Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.649077977Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.64914313Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.649164991Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.649175907Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.649203172Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.650738531Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"101","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.650796761Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.651553694Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.50566246 UTC to 2025-10-20 19:56:09.651553694 UTC +{"at":"2025-10-20T19:56:09.651617956Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.651838428Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.651851898Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.651881734Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"102","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.654125047Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.654427509Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",10.625295565293]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:09.65502189Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.658533394Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.658593173Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.658871089Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.660269602Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.660300647Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.660408526Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.660427546Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.66046233Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.660483299Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.661791066Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"121","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.661839966Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.661926208Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.661938301Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.661965791Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.662535035Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"121","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.662691797Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.663450463Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"121","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.66353772Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.663605725Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.663629608Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.663639834Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.663655518Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.664269735Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.664321592Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.664335425Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.664344571Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.664379437Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"122","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.666502765Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.666893938Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",10.893497875326]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:19.669630724Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.670965446Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.671222903Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.671597184Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.67293344Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.672959229Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.673058035Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.673077108Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.673111334Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.673132061Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.674180902Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"140","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.674242223Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.674335247Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.674347401Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.674392451Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.675068524Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"140","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.675135102Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.675875097Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"140","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.675973747Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676039727Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676062012Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676072932Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676089769Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676736133Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676788674Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676802394Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676812439Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.676839301Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"141","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.678673859Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.679081183Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",12.124562837873]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:29.682076004Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.682779426Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.683154733Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.683463565Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684581816Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684614772Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684728035Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684753282Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684795887Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.684821055Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.685786498Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"160","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.685920666Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.685978495Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"160","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686012114Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686025851Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686044873Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686880743Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686945578Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686970613Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.686981138Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.687010839Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.688759084Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"160","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.688820884Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.689628888Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.68969682Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.689717287Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.689728339Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.689758293Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"161","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.692090116Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.692409081Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",12.126082065723]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:39.693756698Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.696772384Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.697355388Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.697505705Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.699096575Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.699124741Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.701223501Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.701257974Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.701301373Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.701324322Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.702755593Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"179","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.702819327Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.702924355Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.702935951Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.702967378Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.703618649Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"179","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.703671297Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.704460403Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"179","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.70458769Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.704661296Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.704684496Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.704695455Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.70471318Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.705400535Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.705456425Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.705470189Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.705480227Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.70550397Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.707172461Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.707699803Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.70795383Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",10.874163678506]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:49.71818294Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:09.651617956 UTC to 2025-10-20 19:56:49.71818294 UTC +{"at":"2025-10-20T19:56:59.499710648Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:56:59.499621762 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.712595221Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.712781845Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.713078914Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.714801474Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.71483893Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.714994167Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.715023848Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.715076003Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.71510752Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.71645868Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"199","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.716547985Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.716723757Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.716743765Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.716814255Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.71762764Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"199","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.717741021Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.71846875Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"199","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.719226679Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.719327587Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.719364367Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.719393802Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.719426462Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.720755982Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.720832102Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.72085592Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.720871926Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.720910661Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"200","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.723017466Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.723312506Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["0d0e583@863","10f2559@887"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.723716954Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.724212318Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",11.807405303769]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.73376545Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:04.530298458Z","ns":"ChainDB.GCEvent.PerformedGC","data":{"kind":"PerformedGC","slot":{"kind":"SlotNo","slot":795}},"sev":"Debug","thread":"20","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.727952895Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.728049996Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.728605271Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.729960288Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.729987805Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.730069976Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.730091803Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.730119421Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.730138679Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.731239797Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"219","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.731399549Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.731504201Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.731517588Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.731551788Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.732178008Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"219","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.732240977Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.732903058Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"219","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733049167Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733112206Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733133467Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733143375Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733157963Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733743183Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733790077Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733802166Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.733810362Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.73383317Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"220","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.7354659Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.736088202Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",10.821336327831]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:09.738814467Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.740652891Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.740911713Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.741174169Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.742435958Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.742471129Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.742589045Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.742614857Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.74265856Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.742690139Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.743956518Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"238","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.744040707Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.744195384Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.74421768Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.744264582Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.744753642Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"238","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.744992225Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.74587565Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"238","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.745983012Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746067778Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746102388Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746115881Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746138025Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.74685025Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746907008Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746922375Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746932077Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.746965048Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"239","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.749023782Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.74950007Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",10.646106170988]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:19.751535337Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.754077569Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.754271752Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3002"},"remoteAddress":{"address":"127.0.0.1","port":"3001"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.754631368Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.756365151Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.756419711Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.75658807Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.756618602Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.756666399Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.756701674Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.758016452Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"257","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.75810177Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.758278715Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.75829891Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.758346559Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.758904545Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"257","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.758977013Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","blockNo":47,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":863},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.760184711Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"257","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.76050501Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.760701339Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.760732989Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.760746546Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.760770233Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","blockNo":48,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"slot":887},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.761654648Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.76171293Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":47,"headerHash":"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"},"tokenAdded":true},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.761728767Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.761739319Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Debug","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.761768943Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3002 127.0.0.1:3001"}},"sev":"Info","thread":"258","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.764433448Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCooling",null]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.764736868Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.76504557Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3001"},["PeerCold",13.788083242653]]]},"sev":"Warning","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T19:57:29.775055581Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:39.767176349Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"261","host":"pamperito-III"} +{"at":"2025-10-20T19:57:39.786616262Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:49.741947601Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"262","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:59.499710648 UTC to 2025-10-20 19:57:49.741947601 UTC +{"at":"2025-10-20T19:57:49.787186462Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:59.501793854Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:57:59.501651257 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:57:59.788309234Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:09.788935996Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:10.276536343Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T19:58:19.789998864Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:29.790856123Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:39.792029286Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:49.793064792Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:51.555730498Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"266","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.32030726Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"272","host":"pamperito-III"} +{"at":"2025-10-20T19:58:59.50360621Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:58:59.503516693 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:58:59.794054981Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:09.794943339Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:19.796013329Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:29.796908Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:39.797686689Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:49.79911835Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:59.505025746Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:59:59.50491902 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:59:59.799914074Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:09.800631604Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:13.530830968Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"277","host":"pamperito-III"} +{"at":"2025-10-20T20:00:19.801907831Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:29.803010211Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:39.803961873Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:49.80463466Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:59.505551216Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:00:59.505434362 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:00:59.805089997Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:09.80592223Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:19.806657812Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:29.80710443Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:39.807847871Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.809020107Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.506819932Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:01:59.506673461 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.577735477Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"288","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.810237586Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:09.81086027Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:19.811848114Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:29.813489456Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:39.814726723Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:49.815730305Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:53.288174967Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"289","host":"pamperito-III"} +{"at":"2025-10-20T20:02:59.508356818Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:02:59.508240958 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:02:59.816871881Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:09.818721828Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:19.820644635Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:29.822472776Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:39.824610473Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:49.826616433Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:59.509772696Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:03:59.509653924 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:03:59.828193288Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:09.829349694Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:19.830479366Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:29.831758045Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:39.833537631Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:49.834683261Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:59.51118897Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:04:59.511087873 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:04:59.835600686Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.844281823Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"300","host":"pamperito-III"} +{"at":"2025-10-20T20:05:09.837417738Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:19.838541948Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:29.839684387Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:32.05446879Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"301","host":"pamperito-III"} +{"at":"2025-10-20T20:05:39.841035578Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:49.842194626Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:59.498093456Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkExpired","data":{"chunkNos":"[\"15\",\"17\",\"24\",\"25\",\"16\",\"20\",\"22\",\"23\",\"21\",\"18\",\"19\",\"0\",\"8\",\"12\",\"14\",\"13\",\"9\",\"10\",\"11\",\"1\",\"4\",\"6\",\"7\",\"5\",\"2\",\"3\"]","kind":"TracePastChunksExpired","noPastChunks":"0"},"sev":"Debug","thread":"16","host":"pamperito-III"} +{"at":"2025-10-20T20:05:59.512416404Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:05:59.512266545 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:05:59.84394185Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:09.84480584Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:19.846048906Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:29.847567521Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:39.849462103Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:49.850959535Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:59.513195248Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:06:59.513084622 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:06:59.852715401Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:09.853806977Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:19.855345869Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:29.857112043Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:39.858797962Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:49.860308322Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:59.514177551Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:07:59.514075861 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:07:59.861819807Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:09.863460732Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:10.835450255Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"303","host":"pamperito-III"} +{"at":"2025-10-20T20:08:19.864846824Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:29.866316944Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.912943551Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"313","host":"pamperito-III"} +{"at":"2025-10-20T20:08:39.867172255Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:49.867763421Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:59.516518361Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:08:59.51631523 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:08:59.869075951Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:09.870112088Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:19.871087102Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:29.871764176Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:39.872888961Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:49.873682896Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:59.51890769Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:09:59.518753528 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:09:59.87444265Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:09.875486805Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:19.876958589Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:29.878196955Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:39.878682721Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:49.879929288Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:50.716661142Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"315","host":"pamperito-III"} +{"at":"2025-10-20T20:10:59.520085858Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:10:59.519986625 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:10:59.88075885Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:09.88215904Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.532780142Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"325","host":"pamperito-III"} +{"at":"2025-10-20T20:11:19.882882432Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:29.883959472Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:39.885539868Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:49.886443085Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:56.077436691Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:11:59.521420498Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:11:59.521326808 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:11:59.886870593Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:09.887844943Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:19.888354088Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:29.88970927Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:39.891691224Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:49.893825778Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:56.078320781Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActiveBigLedgerPeers","counter":0,"duration":60.000975258,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:12:56.078777902Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:12:59.522624336Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:12:59.522477654 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:12:59.894698834Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:09.89694088Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:19.89939794Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:29.135722597Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"328","host":"pamperito-III"} +{"at":"2025-10-20T20:13:29.900802435Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:57:49.787186462 UTC to 2025-10-20 20:13:29.900802435 UTC +{"at":"2025-10-20T20:13:39.903117703Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:49.904736264Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:59.52449889Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:13:59.524273095 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:13:59.905999017Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:09.907697212Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:16.079914955Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownBigLedgerPeers","counter":0,"duration":80.001212353,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:14:16.080154784Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:14:19.909120597Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:29.910768745Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:39.912663188Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:49.913836657Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:59.526184663Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:14:59.526054235 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:14:59.915711557Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:09.917119133Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:16.081923808Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedBigLedgerPeers","counter":0,"duration":60.001870111,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:15:16.082270745Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:15:19.918742521Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:29.920614822Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:39.922767487Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.077233695Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"338","host":"pamperito-III"} +{"at":"2025-10-20T20:15:49.924523632Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:59.526960204Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:15:59.52685459 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:15:59.92556612Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:07.204611219Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"339","host":"pamperito-III"} +{"at":"2025-10-20T20:16:09.927614054Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:16.08379527Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActivePeers","counter":0,"duration":60.00161373,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:16:16.084063735Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:16:19.929700125Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:29.931880392Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:39.933906069Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:49.935467659Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:59.527944951Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:16:59.527858731 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:16:59.936521993Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:09.938636142Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:19.939825288Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:29.941688592Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:36.085585443Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownPeers","counter":0,"duration":80.001570513,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:17:36.085896427Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:17:39.942789915Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:49.944779209Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:59.528591781Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:17:59.528511464 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:17:59.945733694Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:09.946774564Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:19.948690249Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:29.950357621Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:36.086676815Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedPeers","counter":0,"duration":60.001002035,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:18:39.951421497Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:46.665218556Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"341","host":"pamperito-III"} +{"at":"2025-10-20T20:18:49.952562776Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:59.529917084Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:18:59.529809469 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:18:59.953604955Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:09.955527229Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:19.956730756Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:29.958224773Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:39.959516117Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:49.961226344Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:59.531688296Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:19:59.531514966 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:19:59.962249729Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:09.963142204Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.42770686Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"351","host":"pamperito-III"} +{"at":"2025-10-20T20:20:19.964154588Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:29.965009765Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:39.966106163Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:49.967183295Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:59.53273304Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:20:59.532588669 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:20:59.968654212Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:09.9702318Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:19.971627992Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:28.317271691Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"353","host":"pamperito-III"} +{"at":"2025-10-20T20:21:29.973079084Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:39.973622712Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:49.974600012Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:59.53361004Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:21:59.533541174 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:21:59.975466383Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:09.977015857Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:19.978030966Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:29.978975204Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:39.979853247Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:49.980951921Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:59.534757872Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:22:59.53464058 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:22:59.982396025Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:09.982894732Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:19.983892141Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:29.984718549Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:39.985979164Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:49.987311959Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:59.535719668Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:23:59.535642137 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:23:59.988825318Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:07.050838356Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"356","host":"pamperito-III"} +{"at":"2025-10-20T20:24:09.989846774Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.777482611Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"365","host":"pamperito-III"} +{"at":"2025-10-20T20:24:19.990860869Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:29.991715047Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:39.992898159Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:49.993744581Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:59.537230227Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:24:59.537052735 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:24:59.994895461Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:09.996762861Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:19.998286276Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:29.999694006Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:40.000838223Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:50.003116288Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:59.5380182Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:25:59.537897605 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:26:00.004502697Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:10.006246756Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:20.006853493Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:30.00778074Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:40.01009274Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:48.015593783Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"367","host":"pamperito-III"} +{"at":"2025-10-20T20:26:50.012137369Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:59.539007423Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:26:59.538896876 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:27:00.013695811Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:10.015793416Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.339194935Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.342598874Z","ns":"ChainDB.FollowerEvent.FollowerNoLongerInMem","data":{"kind":"FollowerNoLongerInMem"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.342672134Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"0"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.342701029Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"0"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.342739968Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"0","kind":"TracePastChunkMiss","noPastChunks":"0"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.342981342Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"1"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.34314203Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"1","kind":"TracePastChunkMiss","noPastChunks":"1"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.343290284Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"2"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.34374859Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"2","kind":"TracePastChunkMiss","noPastChunks":"2"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.343925527Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"3"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.34412962Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"3","kind":"TracePastChunkMiss","noPastChunks":"3"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.34429456Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"4"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.344607018Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"4","kind":"TracePastChunkMiss","noPastChunks":"4"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.344759623Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"5"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.344885631Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"5","kind":"TracePastChunkMiss","noPastChunks":"5"},"sev":"Debug","thread":"374","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 20:13:39.903117703 UTC to 2025-10-20 20:27:17.344885631 UTC +{"at":"2025-10-20T20:27:17.345044431Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"6"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.345597752Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"6","kind":"TracePastChunkMiss","noPastChunks":"6"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.345823514Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"7"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.346186073Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"7","kind":"TracePastChunkMiss","noPastChunks":"7"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.346358992Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"8"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.346492246Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"8","kind":"TracePastChunkMiss","noPastChunks":"8"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.346660099Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"9"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.346871321Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"9","kind":"TracePastChunkMiss","noPastChunks":"9"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.349611747Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"10"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.349784987Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"10","kind":"TracePastChunkMiss","noPastChunks":"10"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.349964978Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"11"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.350179039Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"11","kind":"TracePastChunkMiss","noPastChunks":"11"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.350326176Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"12"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.350616196Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"12","kind":"TracePastChunkMiss","noPastChunks":"12"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.350771874Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"13"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.350973526Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"13","kind":"TracePastChunkMiss","noPastChunks":"13"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.351129656Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"14"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.351329054Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"14","kind":"TracePastChunkMiss","noPastChunks":"14"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.351485991Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"15"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.351726454Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"15","kind":"TracePastChunkMiss","noPastChunks":"15"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.35197797Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"16","kind":"TracePastChunkMiss","noPastChunks":"16"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352011744Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 2) 4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 44) bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352060866Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"16"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352090204Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"16"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352125873Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352134323Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352151155Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352224048Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"0","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352341921Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.35238169Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"17","kind":"TracePastChunkMiss","noPastChunks":"17"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.35240588Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"17"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352511992Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"18","kind":"TracePastChunkMiss","noPastChunks":"18"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352677139Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"19"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352812075Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"19","kind":"TracePastChunkMiss","noPastChunks":"19"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.352967536Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"20"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353240374Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"20","kind":"TracePastChunkMiss","noPastChunks":"20"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353394877Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"21"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353511473Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"21","kind":"TracePastChunkMiss","noPastChunks":"21"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353619797Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"22","kind":"TracePastChunkMiss","noPastChunks":"22"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353719749Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"23","kind":"TracePastChunkMiss","noPastChunks":"23"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.353860791Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"24"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354034144Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"24","kind":"TracePastChunkMiss","noPastChunks":"24"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354183595Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"25"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354427624Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkMiss","data":{"chunkNo":"25","kind":"TracePastChunkMiss","noPastChunks":"25"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354572848Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"25","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354685396Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.354737107Z","ns":"ChainDB.ImmDbEvent.CacheEvent.CurrentChunkHit","data":{"chunkNo":"26","kind":"TraceCurrentChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365245644Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 179) a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365314974Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365343996Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365393507Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365416859Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365533309Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"1","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365774858Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365828285Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"2","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.365963413Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.366013656Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"3","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.366188895Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.366236482Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"4","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.366320351Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.366377121Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"5","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.376921069Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 183) 56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 187) 60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.376994423Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.377023226Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.377062257Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.377084512Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.377190318Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387641313Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 188) 48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 222) 0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387712154Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387742008Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387781444Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387802738Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.387896966Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"6","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.388017175Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.38806492Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"7","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397725431Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 247) 85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 280) af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397793248Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397819897Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397858309Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397878081Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.397964454Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"8","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.398080389Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.398127837Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"9","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.422794991Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 304) 05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 362) 9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.422864902Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.422890788Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.422931596Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.422951274Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.423034172Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"10","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.42320294Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.423251121Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"11","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.423509757Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.423558271Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434087613Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 376) a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 397) 521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.43415285Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434177453Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434211278Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434230352Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434311208Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"12","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434443516Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.434488931Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"13","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446148443Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 444) 12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 505) 0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446211582Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446239303Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446279999Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446301124Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446383211Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"14","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.4464956Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"15","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446517849Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.446560255Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"16","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466363309Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 558) 6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 602) a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.46644632Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466476311Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466516839Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466541856Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466633052Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"18","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466758186Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.466812974Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"19","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.467024374Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.467080094Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"20","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479364721Z","ns":"ChainDB.IteratorEvent.StreamFromImmutableDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 707) 435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720)","kind":"StreamFromImmutableDB","to":"StreamToInclusive (RealPoint (SlotNo 728) e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479441575Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479467803Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479505289Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479525112Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479606885Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"23","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479776093Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.479821823Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkHit","data":{"chunkNo":"24","kind":"TracePastChunkHit","noPastChunks":"26"},"sev":"Debug","thread":"379","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 20:27:17.345044431 UTC to 2025-10-20 20:27:17.479821823 UTC +{"at":"2025-10-20T20:27:17.483820503Z","ns":"ChainDB.FollowerEvent.FollowerSwitchToMem","data":{"kind":"FollowerSwitchToMem"},"sev":"Debug","thread":"374","host":"pamperito-III"} +{"at":"2025-10-20T20:27:17.489109567Z","ns":"ChainDB.IteratorEvent.StreamFromVolatileDB","data":{"from":"StreamFromInclusive (RealPoint (SlotNo 740) 120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e)","kind":"StreamFromVolatileDB","point":"[\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740\",\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746\",\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756\",\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795\",\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809\",\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810\",\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829\"]","to":"StreamToInclusive (RealPoint (SlotNo 829) 41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553)"},"sev":"Debug","thread":"379","host":"pamperito-III"} +{"at":"2025-10-20T20:27:20.017728342Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:30.019234268Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:40.021105365Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:50.022808151Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:59.540090542Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:27:59.539962584 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:28:00.024782057Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:02.594162173Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActiveBigLedgerPeers","counter":0,"duration":60.000750568,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:28:02.594892524Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:28:10.025749876Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:20.027503171Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:30.028694587Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:40.030143717Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:50.032335727Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:59.541263894Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:28:59.541089891 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:29:00.033862475Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:10.035168615Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:20.036695064Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:22.594926812Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownBigLedgerPeers","counter":0,"duration":80.000464288,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:29:22.59512567Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:29:28.743535771Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"380","host":"pamperito-III"} +{"at":"2025-10-20T20:29:30.038297924Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:40.039349773Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:50.040976409Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:59.5428291Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:29:59.542669838 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:30:00.042517216Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:10.043724699Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:20.04557841Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:22.59601566Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedBigLedgerPeers","counter":0,"duration":60.000984518,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:30:30.046972564Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:40.04900734Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:49.875208917Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"391","host":"pamperito-III"} +{"at":"2025-10-20T20:30:50.050958363Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:59.543351321Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:30:59.543257758 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:31:00.051742933Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:10.053399462Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:20.054721437Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:22.59875811Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActivePeers","counter":0,"duration":60.002504099,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:31:22.599567016Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:31:30.05582575Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:40.057497152Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:50.058666869Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:59.544717713Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:31:59.54456639 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:32:00.059647119Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:10.0611522Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:10.15994001Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"393","host":"pamperito-III"} +{"at":"2025-10-20T20:32:20.062927894Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:30.064026049Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:40.065191141Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:42.600665536Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownPeers","counter":0,"duration":80.001567198,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:32:42.601100098Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:32:50.066636407Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:59.546217502Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:32:59.546050515 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:33:00.068139307Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:10.069118369Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:20.070319832Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:30.072157819Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:40.073795301Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:42.602180393Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedPeers","counter":0,"duration":60.001376926,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:33:50.074556666Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:59.547578285Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:33:59.547427153 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:34:00.075498824Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:10.076984091Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:20.0781483Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:30.079442993Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:40.080456619Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:50.081854267Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:51.983853143Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"396","host":"pamperito-III"} +{"at":"2025-10-20T20:34:59.549467221Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:34:59.549273871 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:35:00.083213516Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:01.850876598Z","ns":"ChainDB.FollowerEvent.NewFollower","data":{"kind":"NewFollower"},"sev":"Debug","thread":"405","host":"pamperito-III"} +{"at":"2025-10-20T20:35:10.083920951Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:20.084742037Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.086462302Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300208806Z","ns":"Net.Server.Local.Error","data":{"kind":"ServerError","reason":"AsyncCancelled"},"sev":"Critical","thread":"50","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300354653Z","ns":"Net.Server.Remote.Error","data":{"kind":"ServerError","reason":"AsyncCancelled"},"sev":"Critical","thread":"47","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300412181Z","ns":"Net.Server.Remote.Stopped","data":{"kind":"ServerStopped"},"sev":"Notice","thread":"36","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300716518Z","ns":"Net.Server.Local.Stopped","data":{"kind":"ServerStopped"},"sev":"Notice","thread":"37","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300765992Z","ns":"Net.PeerSelection.Selection.OutboundGovernorCriticalFailure","data":{"kind":"OutboundGovernorCriticalFailure","reason":"AsyncCancelled"},"sev":"Error","thread":"46","host":"pamperito-III"} diff --git a/scripts/leios-demo/data/cardano-node-1.log b/scripts/leios-demo/data/cardano-node-1.log new file mode 100644 index 0000000000..0b93623bde --- /dev/null +++ b/scripts/leios-demo/data/cardano-node-1.log @@ -0,0 +1,1852 @@ +Resolving dependencies... +Node configuration: NodeConfiguration {ncSocketConfig = SocketConfig {ncNodeIPv4Addr = Last {getLast = Just 0.0.0.0}, ncNodeIPv6Addr = Last {getLast = Nothing}, ncNodePortNumber = Last {getLast = Just 3003}, ncSocketPath = Last {getLast = Just "node-1.socket"}}, ncConfigFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/config.json", ncTopologyFile = "topology-node-1.json", ncDatabaseFile = OnePathForAllDbs "/tmp/tmp.HodA1h2aAY/node-1/db", ncProtocolFiles = ProtocolFilepaths {byronCertFile = Nothing, byronKeyFile = Nothing, shelleyKESFile = Nothing, shelleyVRFFile = Nothing, shelleyCertFile = Nothing, shelleyBulkCredsFile = Nothing}, ncValidateDB = False, ncShutdownConfig = ShutdownConfig {scIPC = Nothing, scOnSyncLimit = Just NoShutdown}, ncStartAsNonProducingNode = False, ncProtocolConfig = NodeProtocolConfigurationCardano (NodeByronProtocolConfiguration {npcByronGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/byron/genesis.json", npcByronGenesisFileHash = Nothing, npcByronReqNetworkMagic = RequiresMagic, npcByronPbftSignatureThresh = Nothing, npcByronSupportedProtocolVersionMajor = 3, npcByronSupportedProtocolVersionMinor = 0, npcByronSupportedProtocolVersionAlt = 0}) (NodeShelleyProtocolConfiguration {npcShelleyGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis-shelley.json", npcShelleyGenesisFileHash = Nothing}) (NodeAlonzoProtocolConfiguration {npcAlonzoGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis.alonzo.json", npcAlonzoGenesisFileHash = Nothing}) (NodeConwayProtocolConfiguration {npcConwayGenesisFile = "/home/damian/Downloads/2025-10-08-19-42-9d25e-1050-50-blocks-50-coay-sup/node-0/../genesis/genesis.conway.json", npcConwayGenesisFileHash = Nothing}) (NodeHardForkProtocolConfiguration {npcExperimentalHardForksEnabled = True, npcTestShelleyHardForkAtEpoch = Just (EpochNo 0), npcTestShelleyHardForkAtVersion = Nothing, npcTestAllegraHardForkAtEpoch = Just (EpochNo 0), npcTestAllegraHardForkAtVersion = Nothing, npcTestMaryHardForkAtEpoch = Just (EpochNo 0), npcTestMaryHardForkAtVersion = Nothing, npcTestAlonzoHardForkAtEpoch = Just (EpochNo 0), npcTestAlonzoHardForkAtVersion = Nothing, npcTestBabbageHardForkAtEpoch = Just (EpochNo 0), npcTestBabbageHardForkAtVersion = Nothing, npcTestConwayHardForkAtEpoch = Just (EpochNo 0), npcTestConwayHardForkAtVersion = Nothing}) (NodeCheckpointsConfiguration {npcCheckpointsFile = Nothing, npcCheckpointsFileHash = Nothing}), ncDiffusionMode = InitiatorAndResponderDiffusionMode, ncExperimentalProtocolsEnabled = True, ncMaxConcurrencyBulkSync = Nothing, ncMaxConcurrencyDeadline = Nothing, ncLoggingSwitch = True, ncLogMetrics = True, ncTraceConfig = TraceDispatcher (TraceSelection {traceVerbosity = NormalVerbosity, traceAcceptPolicy = OnOff {isOn = False}, traceBlockFetchClient = OnOff {isOn = False}, traceBlockFetchDecisions = OnOff {isOn = True}, traceBlockFetchProtocol = OnOff {isOn = False}, traceBlockFetchProtocolSerialised = OnOff {isOn = False}, traceBlockFetchServer = OnOff {isOn = False}, traceBlockchainTime = OnOff {isOn = False}, traceChainDB = OnOff {isOn = True}, traceChainSyncBlockServer = OnOff {isOn = False}, traceChainSyncClient = OnOff {isOn = True}, traceChainSyncHeaderServer = OnOff {isOn = False}, traceChainSyncProtocol = OnOff {isOn = False}, traceConnectionManager = OnOff {isOn = True}, traceConnectionManagerCounters = OnOff {isOn = True}, traceConnectionManagerTransitions = OnOff {isOn = False}, traceDebugPeerSelectionInitiatorTracer = OnOff {isOn = False}, traceDebugPeerSelectionInitiatorResponderTracer = OnOff {isOn = False}, traceDiffusionInitialization = OnOff {isOn = False}, traceDnsResolver = OnOff {isOn = False}, traceDnsSubscription = OnOff {isOn = True}, traceErrorPolicy = OnOff {isOn = True}, traceForge = OnOff {isOn = True}, traceForgeStateInfo = OnOff {isOn = True}, traceGDD = OnOff {isOn = False}, traceHandshake = OnOff {isOn = False}, traceInboundGovernor = OnOff {isOn = True}, traceInboundGovernorCounters = OnOff {isOn = True}, traceInboundGovernorTransitions = OnOff {isOn = True}, traceIpSubscription = OnOff {isOn = True}, traceKeepAliveClient = OnOff {isOn = False}, traceLedgerPeers = OnOff {isOn = False}, traceLocalChainSyncProtocol = OnOff {isOn = False}, traceLocalConnectionManager = OnOff {isOn = True}, traceLocalErrorPolicy = OnOff {isOn = True}, traceLocalHandshake = OnOff {isOn = True}, traceLocalInboundGovernor = OnOff {isOn = True}, traceLocalMux = OnOff {isOn = False}, traceLocalRootPeers = OnOff {isOn = False}, traceLocalServer = OnOff {isOn = True}, traceLocalStateQueryProtocol = OnOff {isOn = False}, traceLocalTxMonitorProtocol = OnOff {isOn = False}, traceLocalTxSubmissionProtocol = OnOff {isOn = False}, traceLocalTxSubmissionServer = OnOff {isOn = False}, traceMempool = OnOff {isOn = True}, traceBackingStore = OnOff {isOn = False}, traceMux = OnOff {isOn = True}, tracePeerSelection = OnOff {isOn = True}, tracePeerSelectionCounters = OnOff {isOn = True}, tracePeerSelectionActions = OnOff {isOn = True}, tracePublicRootPeers = OnOff {isOn = False}, traceSanityCheckIssue = OnOff {isOn = False}, traceServer = OnOff {isOn = True}, traceTxInbound = OnOff {isOn = False}, traceTxOutbound = OnOff {isOn = False}, traceTxSubmissionProtocol = OnOff {isOn = False}, traceTxSubmission2Protocol = OnOff {isOn = False}, traceKeepAliveProtocol = OnOff {isOn = False}, tracePeerSharingProtocol = OnOff {isOn = False}, traceGsm = OnOff {isOn = True}, traceCsj = OnOff {isOn = True}, traceDevotedBlockFetch = OnOff {isOn = True}}), ncTraceForwardSocket = Nothing, ncMaybeMempoolCapacityOverride = Nothing, ncLedgerDbConfig = LedgerDbConfiguration DefaultNumOfDiskSnapshots (RequestedSnapshotInterval 4230s) DefaultQueryBatchSize V2InMemory (DeprecatedOptions ["SnapshotInterval"]), ncProtocolIdleTimeout = 5s, ncTimeWaitTimeout = 60s, ncEgressPollInterval = 0s, ncChainSyncIdleTimeout = TimeoutOverride 0s, ncAcceptedConnectionsLimit = AcceptedConnectionsLimit {acceptedConnectionsHardLimit = 512, acceptedConnectionsSoftLimit = 384, acceptedConnectionsDelay = 5s}, ncDeadlineTargetOfRootPeers = 60, ncDeadlineTargetOfKnownPeers = 150, ncDeadlineTargetOfEstablishedPeers = 40, ncDeadlineTargetOfActivePeers = 15, ncDeadlineTargetOfKnownBigLedgerPeers = 15, ncDeadlineTargetOfEstablishedBigLedgerPeers = 10, ncDeadlineTargetOfActiveBigLedgerPeers = 5, ncSyncTargetOfRootPeers = 0, ncSyncTargetOfKnownPeers = 150, ncSyncTargetOfEstablishedPeers = 40, ncSyncTargetOfActivePeers = 15, ncSyncTargetOfKnownBigLedgerPeers = 100, ncSyncTargetOfEstablishedBigLedgerPeers = 40, ncSyncTargetOfActiveBigLedgerPeers = 30, ncConsensusMode = PraosMode, ncMinBigLedgerPeersForTrustedState = NumberOfBigLedgerPeers {getNumberOfBigLedgerPeers = 5}, ncEnableP2P = EnabledP2PMode, ncPeerSharing = PeerSharingDisabled, ncGenesisConfig = GenesisConfig {gcBlockFetchConfig = GenesisBlockFetchConfiguration {gbfcGracePeriod = 0s}, gcChainSyncLoPBucketConfig = ChainSyncLoPBucketDisabled, gcCSJConfig = CSJDisabled, gcLoEAndGDDConfig = LoEAndGDDDisabled, gcHistoricityCutoff = Nothing}, ncResponderCoreAffinityPolicy = NoResponderCoreAffinity} +{"at":"2025-10-20T19:55:59.465273828Z","ns":"Reflection.TracerInfo","data":{"allTracers":" BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockFetch.Server BlockchainTime ChainDB ChainDB.ReplayBlock ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised ChainSync.ServerBlock ChainSync.ServerHeader Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup Forge.Loop Forge.StateInfo Forge.Stats KeepAlive.Remote Mempool Net Net.Churn Net.ConnectionManager.Local Net.ConnectionManager.Remote Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Local Net.InboundGovernor.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.PeerSelection.Selection Net.Peers.Ledger Net.Peers.List Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxInbound TxSubmission.TxOutbound Version","kind":"TracerMeta","noMetrics":"BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockchainTime ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup KeepAlive.Remote Net Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.Ledger Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound","silentTracers":" BlockFetch.Remote.Serialised ChainDB.ReplayBlock ChainSync.Remote.Serialised ChainSync.ServerBlock ChainSync.ServerHeader Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Forge.StateInfo Forge.Stats KeepAlive.Remote Net Net.Churn Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.PeerSelection Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.Ledger Net.Peers.List PeerSharing.Remote TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound"},"sev":"Notice","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.466148962Z","ns":"Reflection.TracerConfigInfo","data":{"conf":{"TraceOptionForwarder":{"tofConnQueueSize":64,"tofDisconnQueueSize":128,"tofMaxReconnectDelay":30,"tofVerbosity":"Minimum"},"TraceOptionLedgerMetricsFrequency":null,"TraceOptionMetricsPrefix":"cardano.node.metrics.","TraceOptionNodeName":"node-0","TraceOptionPeerFrequency":2000,"TraceOptionResourceFrequency":1000,"TraceOptions":{"":{"backends":["Stdout MachineFormat","EKGBackend","Forwarder"],"detail":"DNormal","severity":"Notice"},"BlockFetch.Client":{"severity":"Debug"},"BlockFetch.Decision":{"severity":"Debug"},"BlockFetch.Remote":{"severity":"Debug"},"BlockFetch.Remote.Serialised":{"severity":"Notice"},"BlockFetch.Server":{"severity":"Notice"},"BlockchainTime":{"severity":"Notice"},"ChainDB":{"severity":"Debug"},"ChainDB.AddBlockEvent.AddBlockValidation":{"severity":"Debug"},"ChainDB.LedgerEvent.Flavor.V1.OnDisk.BackingStoreEvent":{"severity":"Silence"},"ChainDB.LedgerEvent.Forker":{"severity":"Notice"},"ChainDB.ReplayBlock.LedgerReplay":{"severity":"Notice"},"ChainSync.Client":{"severity":"Debug"},"ChainSync.Local":{"severity":"Debug"},"ChainSync.Remote":{"severity":"Debug"},"ChainSync.Remote.Serialised":{"severity":"Notice"},"ChainSync.ServerBlock":{"severity":"Notice"},"ChainSync.ServerHeader":{"severity":"Notice"},"Consensus.GSM":{"severity":"Info"},"Forge.Loop":{"severity":"Notice"},"Forge.StateInfo":{"severity":"Notice"},"LedgerMetrics":{"severity":"Info"},"Mempool":{"severity":"Notice"},"Mempool.AttemptAdd":{"severity":"Silence"},"Mempool.LedgerFound":{"severity":"Silence"},"Mempool.LedgerNotFound":{"severity":"Notice"},"Mempool.SyncNotNeeded":{"severity":"Silence"},"Mempool.Synced":{"severity":"Silence"},"Net":{"severity":"Notice"},"Net.AcceptPolicy":{"severity":"Notice"},"Net.ConnectionManager.Local":{"severity":"Notice"},"Net.ConnectionManager.Remote":{"severity":"Notice"},"Net.ConnectionManager.Remote.ConnectionManagerCounters":{"severity":"Notice"},"Net.DNSResolver":{"severity":"Notice"},"Net.ErrorPolicy":{"severity":"Info"},"Net.ErrorPolicy.Local":{"severity":"Notice"},"Net.ErrorPolicy.Remote":{"severity":"Notice"},"Net.Handshake.Local":{"severity":"Notice"},"Net.Handshake.Remote":{"severity":"Notice"},"Net.InboundGovernor":{"severity":"Warning"},"Net.InboundGovernor.Local":{"severity":"Notice"},"Net.InboundGovernor.Remote":{"severity":"Notice"},"Net.InboundGovernor.Transition":{"severity":"Notice"},"Net.Mux.Local":{"severity":"Notice"},"Net.Mux.Remote":{"severity":"Notice"},"Net.PeerSelection":{"severity":"Notice"},"Net.PeerSelection.Actions":{"severity":"Notice"},"Net.PeerSelection.Counters":{"detail":"DMinimal","severity":"Notice"},"Net.PeerSelection.Initiator":{"severity":"Notice"},"Net.PeerSelection.Responder":{"severity":"Notice"},"Net.PeerSelection.Selection":{"severity":"Notice"},"Net.Peers.Ledger":{"severity":"Notice"},"Net.Peers.List":{"severity":"Notice"},"Net.Peers.LocalRoot":{"severity":"Notice"},"Net.Peers.PublicRoot":{"severity":"Notice"},"Net.Server.Local":{"severity":"Notice"},"Net.Server.Remote":{"severity":"Notice"},"Net.Subscription.DNS":{"severity":"Notice"},"Net.Subscription.IP":{"severity":"Notice"},"NodeState":{"severity":"Notice"},"Resources":{"severity":"Notice"},"Shutdown":{"severity":"Notice"},"Startup":{"severity":"Notice"},"Startup.DiffusionInit":{"severity":"Notice"},"StateQueryServer":{"severity":"Notice"},"TxSubmission.Local":{"severity":"Notice"},"TxSubmission.LocalServer":{"severity":"Notice"},"TxSubmission.MonitorClient":{"severity":"Notice"},"TxSubmission.Remote":{"severity":"Notice"},"TxSubmission.TxInbound":{"severity":"Notice"},"TxSubmission.TxOutbound":{"severity":"Notice"},"Version.NodeVersion":{"severity":"Info"}}}},"sev":"Notice","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.466168099Z","ns":"Version.NodeVersion","data":{"applicationName":"cardano-node","applicationVersion":"10.5.1","architecture":"x86_64","compilerName":"ghc","compilerVersion":"9.6.7","gitRevision":"ca1ec278070baf4481564a6ba7b4a5b9e3d9f366","osName":"linux"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.469856964Z","ns":"Startup.MovedTopLevelOption","data":{"kind":"MovedTopLevelOption","option":"SnapshotInterval"},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.472611675Z","ns":"ChainDB.LastShutdownUnclean","data":{"kind":"LastShutdownUnclean"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.472686684Z","ns":"ChainDB.OpenEvent.StartedOpeningDB","data":{"kind":"StartedOpeningDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.472698917Z","ns":"ChainDB.OpenEvent.StartedOpeningImmutableDB","data":{"kind":"StartedOpeningImmutableDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.472988695Z","ns":"ChainDB.ImmDbEvent.NoValidLastLocation","data":{"kind":"NoValidLastLocation"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.47312448Z","ns":"ChainDB.OpenEvent.OpenedImmutableDB","data":{"epoch":"0","immtip":{"kind":"GenesisPoint"},"kind":"OpenedImmutableDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.473140005Z","ns":"ChainDB.OpenEvent.StartedOpeningVolatileDB","data":{"kind":"StartedOpeningVolatileDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.473254653Z","ns":"ChainDB.OpenEvent.OpenedVolatileDB","data":{"kind":"OpenedVolatileDB","maxSlotNo":"NoMaxSlotNo"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.47326994Z","ns":"ChainDB.OpenEvent.StartedOpeningLgrDB","data":{"kind":"StartedOpeningLgrDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.47331127Z","ns":"ChainDB.LedgerEvent.Replay.ReplayStart.ReplayFromGenesis","data":{"kind":"ReplayFromGenesis"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474002264Z","ns":"ChainDB.OpenEvent.OpenedLgrDB","data":{"kind":"OpenedLgrDB"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474025249Z","ns":"ChainDB.InitChainSelEvent.StartedInitChainSelection","data":{"kind":"Follower.StartedInitChainSelection"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474095752Z","ns":"ChainDB.InitChainSelEvent.InitialChainSelected","data":{"kind":"Follower.InitialChainSelected"},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474184995Z","ns":"ChainDB.OpenEvent.OpenedDB","data":{"immtip":{"kind":"GenesisPoint"},"kind":"OpenedDB","tip":{"kind":"GenesisPoint"}},"sev":"Info","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474362361Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.474743714Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:55:59.474712925 UTC"},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.475203503Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.475290235Z","ns":"Shutdown.ArmedAt","data":{"kind":"ShutdownArmedAt","limit":{"tag":"NoShutdown"}},"sev":"Warning","thread":"5","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.475583937Z","ns":"Net.Server.Remote.Started","data":{"addresses":[{"addr":"0.0.0.0","port":"3003"}],"kind":"AcceptPolicyTrace"},"sev":"Notice","thread":"36","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.475594902Z","ns":"Net.Server.Local.Started","data":{"addresses":[{"path":"node-1.socket"}],"kind":"AcceptPolicyTrace"},"sev":"Notice","thread":"37","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.475853712Z","ns":"Net.PeerSelection.Selection.UseBootstrapPeersChanged","data":{"kind":"UseBootstrapPeersChanged","useBootstrapPeers":[]},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.476076071Z","ns":"Consensus.GSM.GsmEventPreSyncingToSyncing","data":{"kind":"GsmEventPreSyncingToSyncing"},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.476136584Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":0},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":0,"targetActivePeers":0,"targetEstablishedBigLedgerPeers":0,"targetEstablishedPeers":0,"targetKnownBigLedgerPeers":0,"targetKnownPeers":0,"targetRootPeers":0}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.476269916Z","ns":"Net.PeerSelection.Selection.LocalRootPeersChanged","data":{"current":{"groups":[[1,1,[[{"address":"127.0.0.1","port":"3002"},{"diffusionMode":"InitiatorAndResponderDiffusionMode","extraFlags":"IsTrustable","peerAdvertise":false}]]]],"kind":"LocalRootPeers"},"kind":"LocalRootPeersChanged","previous":{"groups":[],"kind":"LocalRootPeers"}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:55:59.476838073Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : does not exist (Connection refused)","kind":"AcquireConnectionError"},"sev":"Error","thread":"52","host":"pamperito-III"} +{"at":"2025-10-20T19:56:02.477183392Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":0}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.498418659Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.498746705Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499047151Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499853854Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499874824Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499908557Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499922677Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499946532Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499963831Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499979229Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.499990185Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50000063Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500020889Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500034639Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500044578Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500054806Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500065122Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50007786Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500088121Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500097974Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500121086Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500134138Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500143475Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500153832Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500163757Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500176617Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500186753Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500196887Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500207057Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500220232Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5002309Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500241144Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500251401Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500263957Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50027419Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500284598Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500294967Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500309236Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500320029Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500330284Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500340494Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500353781Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500364242Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500382929Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500393109Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500406207Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500417089Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500427633Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500437901Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500450955Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500461675Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.500472104Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.501503772Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503310991Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"kind":"GenesisPoint"}},"sev":"Notice","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503335935Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503345616Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503376258Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503465899Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503543421Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503589515Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50362976Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503626687Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","blockNo":0,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":2},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50367115Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503707921Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503739302Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503771828Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503803843Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503833219Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503869051Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503902494Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.503935837Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:55:59.465273828 UTC to 2025-10-20 19:56:04.505378497 UTC +{"at":"2025-10-20T19:56:04.503971064Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504006264Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50403748Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504071562Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504109566Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504141369Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504176208Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504209799Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504239524Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504272472Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504308292Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50433664Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504375217Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504408222Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50443681Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504485269Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504518455Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504534779Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504551163Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504578306Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":false},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504581982Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504610494Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504613628Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504622784Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.504641998Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","blockNo":1,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":44},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505295371Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505357203Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":0,"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505378497Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505388422Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.505598686Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","blockNo":2,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":52},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506242837Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506288434Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":1,"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50630366Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506312124Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506326155Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","blockNo":3,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":53},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506947988Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.506986128Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":2,"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507000043Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507008881Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507023562Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","blockNo":4,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":59},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507520172Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507574614Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507614378Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507641611Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507647497Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507679884Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":3,"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507681501Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507694383Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507703513Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507713129Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50771593Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","blockNo":5,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":77},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507740913Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507771939Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507802348Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507828352Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507859301Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.507890601Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.508326415Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.508364501Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":4,"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.508383389Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.508392027Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.508404938Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","blockNo":6,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":80},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.50900864Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.509056807Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":5,"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.509070137Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.509078242Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.509089944Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","blockNo":7,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":95},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.509533358Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["4e93dab@2","bd384ce@44","23b021f@52","5ecd12b@53","0341e87@59","312446d@77","b69dee5@80"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510056598Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510296941Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510328518Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51036412Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"SendFetchRequest","length":7,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510413652Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510477586Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":6,"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510496592Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.510506879Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51052267Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","blockNo":8,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":108},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511228682Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511275865Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":7,"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511291606Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511300518Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511313098Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","blockNo":9,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":111},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511947414Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.511991968Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":8,"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512005594Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51201392Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512026573Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","blockNo":10,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":148},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512518318Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512536359Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512643527Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512683395Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":9,"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512697417Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512706318Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.512718827Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","blockNo":11,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":162},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513278714Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","blockSize":1033,"kind":"MsgBlock","txIds":["c3b5fef45f23b1ae942b9386e42f70a3c83aab8ef8fe95054c3f27cfb3cd32a6"]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513501091Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513542618Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513585392Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","delay":1037548.513300015,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":1033},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513688376Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513742759Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513762754Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513789188Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","delay":1037506.513694563,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513839554Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513882405Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513897884Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513920571Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","delay":1037498.513843317,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.513960474Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514001437Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514020726Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514040221Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","delay":1037497.513963907,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514081841Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514125894Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514141137Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514163352Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","delay":1037491.514086675,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514201608Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514242612Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514260298Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514279048Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","delay":1037473.514205282,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514318625Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514358956Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514552601Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514660283Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":10,"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514683955Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.514695443Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51471459Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","blockNo":12,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":179},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517521829Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517549433Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517595055Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","delay":1037470.514322032,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517616394Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":11,"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51763747Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517648361Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517651898Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517664278Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517665088Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","blockNo":13,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":183},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517683755Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517698054Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5177298Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":183},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517732696Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"blockNo":"0","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517845331Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"blockNo":"0","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517921743Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"kind":"GenesisPoint"}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517943158Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"Point","slot":2},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517979126Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.517986656Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51803812Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","targetBlock":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519505646Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519547221Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519627526Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":0,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":2,"tieBreakVRF":"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf"},"newtip":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2"},"sev":"Notice","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.505388422 UTC to 2025-10-20 19:56:04.52002986 UTC +{"at":"2025-10-20T19:56:04.519715946Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519783392Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519796727Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519827618Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"blockNo":"1","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.51990029Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"blockNo":"1","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519962108Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.519983857Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"Point","slot":44},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.520022464Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52002986Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.520074856Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","targetBlock":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.520774193Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["f0c284a@95","b986a90@108","8a9fdda@111","b0c2dd7@148","5fc55ce@162","a1ad392@179"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521273071Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521320186Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521336035Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"SendFetchRequest","length":6,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.521361486Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522256394Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522280061Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52236517Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522467493Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522503726Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"AddedBlockToQueue","queueSize":6},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52254968Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","delay":1037455.522389671,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52262319Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522680891Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522710232Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52274614Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","delay":1037442.522631187,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52281713Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522869612Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522896728Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"AddedBlockToQueue","queueSize":8},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.522931207Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","delay":1037439.522823689,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523004416Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523054055Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523080966Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"AddedBlockToQueue","queueSize":9},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523097334Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523113117Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","delay":1037402.523011014,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523128911Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523170932Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523218222Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":1,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":44,"tieBreakVRF":"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951"},"newtip":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","oldTipSelectView":{"chainLength":0,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":2,"tieBreakVRF":"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523219717Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523245303Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"AddedBlockToQueue","queueSize":10},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523277033Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","delay":1037388.523177535,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523280427Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523335145Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523340148Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523352551Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523382083Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"blockNo":"2","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523396356Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523424472Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"AddedBlockToQueue","queueSize":10},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523449937Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"blockNo":"2","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52345726Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","delay":1037371.523341796,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523491898Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523499964Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523505718Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523518977Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"Point","slot":52},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523553642Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523561193Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.523801154Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":183},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.524450676Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.524509381Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":12,"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.524529985Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.524540792Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.524557579Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","blockNo":14,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":187},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525190163Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525239412Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":13,"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525254197Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525263987Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525277365Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","blockNo":15,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":188},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525763053Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","targetBlock":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525897421Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.52594292Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":14,"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525956571Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525965531Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.525978441Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","blockNo":16,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":222},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526588711Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526634321Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":15,"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526647828Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526656717Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526669534Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","blockNo":17,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":247},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.526722495Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":247},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528011822Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528039986Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528122156Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":2,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":52,"tieBreakVRF":"a7ebd222c942746c013165f0adc2abfec5f1d25f7b41b2aef928ab4c865f1b48775a18e1699e447b118e89591d663968990ef90f7807b5b2a4295561b0264d69"},"newtip":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","oldTipSelectView":{"chainLength":1,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":44,"tieBreakVRF":"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528213747Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528270054Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528282093Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528304277Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"blockNo":"3","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528378048Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"blockNo":"3","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528426072Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"kind":"GenesisPoint"},"head":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528445965Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"Point","slot":53},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528480994Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.528488899Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.529799718Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","targetBlock":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531170916Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531211433Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531318958Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":3,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":53,"tieBreakVRF":"4c0c5eb5ba7015fe3da918899131fbe585560db7ba3df5f6e3fef69c9b8e545b86914011d4d69c2d143b66a9f87def6276d775988281818c071068320a0b045a"},"newtip":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","oldTipSelectView":{"chainLength":2,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":52,"tieBreakVRF":"a7ebd222c942746c013165f0adc2abfec5f1d25f7b41b2aef928ab4c865f1b48775a18e1699e447b118e89591d663968990ef90f7807b5b2a4295561b0264d69"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531417327Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531484946Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531498097Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531538392Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"blockNo":"4","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531633836Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"blockNo":"4","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531706927Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2},"head":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531726084Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"Point","slot":59},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531764556Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.531772783Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.532515875Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8","kind":"BlockPoint","slot":2}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.532543838Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":2}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.532600864Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","targetBlock":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.533240558Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["56515bf@183","60fd8fc@187","48cf5b4@188","0a723e7@222"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.533752248Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534027741Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534067574Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534178309Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":4,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":59,"tieBreakVRF":"263b9f9d16d7bf1a7f540d257bf74e4f86c172719b84db889be808775165cab9872c9e985c644f01a2a987be20e9e730e3033ca4adb3bf55122941675ea8a8a4"},"newtip":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","oldTipSelectView":{"chainLength":3,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":53,"tieBreakVRF":"4c0c5eb5ba7015fe3da918899131fbe585560db7ba3df5f6e3fef69c9b8e545b86914011d4d69c2d143b66a9f87def6276d775988281818c071068320a0b045a"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534258688Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534324407Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534337433Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534391397Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"blockNo":"5","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534469569Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"blockNo":"5","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534541295Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44},"head":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534560432Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"Point","slot":77},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534597487Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53460564Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534821968Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534843094Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.534877664Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.535543446Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4","kind":"BlockPoint","slot":44}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.535571353Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":44}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.535629429Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","targetBlock":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.536884156Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.536929834Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537056665Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537126049Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53714022Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537184593Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"blockNo":"6","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537271178Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"blockNo":"6","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537351895Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52},"head":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53738534Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"Point","slot":80},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537427581Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.537437234Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.520074856 UTC to 2025-10-20 19:56:04.537437234 UTC +{"at":"2025-10-20T19:56:04.537876632Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8","kind":"BlockPoint","slot":52}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.538022335Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":52}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.538097781Z","ns":"ChainDB.LedgerEvent.Snapshot.TookSnapshot","data":{"enclosedTime":{"tag":"RisingEdge"},"kind":"TookSnapshot","snapshot":{"kind":"snapshot"},"tip":"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8"},"sev":"Info","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.538877043Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":247},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.538955498Z","ns":"ChainDB.LedgerEvent.Snapshot.TookSnapshot","data":{"enclosedTime":{"contents":8.49654e-4,"tag":"FallingEdgeWith"},"kind":"TookSnapshot","snapshot":{"kind":"snapshot"},"tip":"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8"},"sev":"Info","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53911561Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539131958Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539197438Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539261248Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.53928494Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539323733Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","delay":1037367.539203893,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539392549Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539428543Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539444303Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"AddedBlockToQueue","queueSize":8},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539465563Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","delay":1037363.539397139,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539463957Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","targetBlock":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539506364Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539539759Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539555699Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"AddedBlockToQueue","queueSize":9},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539576825Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","delay":1037362.539510402,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539616278Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539660252Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539675608Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"AddedBlockToQueue","queueSize":10},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539698926Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","delay":1037328.539620059,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539720747Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.539730961Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540264061Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540387633Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":16,"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540422884Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540436156Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540459421Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","blockNo":18,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":280},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540597579Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":280},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540845862Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540876079Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.540992757Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541059802Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541075879Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541117967Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"blockNo":"7","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541196882Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"blockNo":"7","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541270813Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53},"head":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541291083Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"Point","slot":95},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541328334Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541336809Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541473474Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59","kind":"BlockPoint","slot":53}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.541500974Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":53}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.543969997Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","targetBlock":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.544658843Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["85d81d9@247"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545051999Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545082998Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545092762Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545113219Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"SendFetchRequest","length":1,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54511598Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54514253Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545239339Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545308438Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545322713Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545364566Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"blockNo":"8","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545464366Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"blockNo":"8","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545540163Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59},"head":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545561819Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"Point","slot":108},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545599554Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545608969Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.545992181Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e","kind":"BlockPoint","slot":59}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.546013505Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":59}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547223605Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547241574Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547303959Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","blockSize":862,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54739775Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547422887Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"AddedBlockToQueue","queueSize":9},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547458196Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","delay":1037303.547308576,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":862},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.547488668Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54749845Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.548009139Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","targetBlock":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549017934Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549055371Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549180516Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549248673Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549262499Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549310686Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"blockNo":"9","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54979434Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"blockNo":"9","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549817249Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":280},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.54988282Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77},"head":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549907633Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"Point","slot":111},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549947553Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.549955821Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.559186342Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","targetBlock":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560424817Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560506792Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":17,"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560536225Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560550205Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560561637Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560572313Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","blockNo":19,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":304},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560605039Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560687871Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":304},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560758916Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560833911Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560851719Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560907758Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37","kind":"BlockPoint","slot":77}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.560933999Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"blockNo":"10","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56094054Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":77}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561028896Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"blockNo":"10","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561116326Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80},"head":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561140092Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"Point","slot":148},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561188712Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561197649Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561345817Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a","kind":"BlockPoint","slot":80}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561376787Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":80}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56165142Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["af465fe@280"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.561955687Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.562317292Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.562341763Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"SendFetchRequest","length":1,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.562397676Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56284531Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","targetBlock":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564001492Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564040945Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564170499Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564238526Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564256317Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564302544Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"blockNo":"11","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564395338Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"blockNo":"11","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564476773Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95},"head":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564501486Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"Point","slot":162},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564542762Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.564551923Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56543631Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":304},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.566091023Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068","kind":"BlockPoint","slot":95}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.566124467Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":95}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.566217077Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.537876632 UTC to 2025-10-20 19:56:04.566217077 UTC +{"at":"2025-10-20T19:56:04.566280593Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":18,"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.566442091Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.566457006Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56647885Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","blockNo":20,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":325},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567295298Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567352309Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":19,"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567357101Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","targetBlock":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567380508Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567391779Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56740723Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","blockNo":21,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":333},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.567468353Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":333},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.568181887Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.568207438Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56829304Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56838855Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.568415796Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"AddedBlockToQueue","queueSize":7},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.56845545Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","delay":1037270.568298194,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.568496205Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.568507976Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569021627Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569106606Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569752785Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569832839Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569848527Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569898943Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"blockNo":"12","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.569985667Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"blockNo":"12","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57003496Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":333},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.570075014Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108},"head":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.570100191Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"Point","slot":179},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57014525Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.570154989Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.570446705Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","targetBlock":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571255006Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908","kind":"BlockPoint","slot":108}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571282809Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":108}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571680447Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571745493Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":20,"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571769019Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571781197Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571803482Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","blockNo":22,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":351},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.571883422Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":351},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57197476Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["05f2b94@304","a55ea78@325","81087aa@333"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572082446Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572122356Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572259724Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572330728Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57234449Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572356749Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572407295Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"blockNo":"13","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572492713Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"blockNo":"13","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572573822Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111},"head":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572597972Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"Point","slot":183},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572602344Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":351},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572640227Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572649233Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.572727845Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","targetBlock":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.573731294Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.573812967Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":21,"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57383667Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.573849141Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.573868415Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","blockNo":23,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":357},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574273669Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574318225Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574452188Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57451876Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574532472Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574605427Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"blockNo":"14","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57469854Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"blockNo":"14","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574804714Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148},"head":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57482858Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"Point","slot":187},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574872212Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574881128Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574882798Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828","kind":"BlockPoint","slot":111}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.574910073Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":111}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.575399689Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5754637Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":22,"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.575484755Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.575495742Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.575513266Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","blockNo":24,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":362},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.575935101Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","targetBlock":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576524187Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0","kind":"BlockPoint","slot":148}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576551458Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":148}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576630364Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576686444Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":23,"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576704481Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576715064Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576730987Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","blockNo":25,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":376},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576797693Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":376},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576846077Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57686444Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"SendFetchRequest","length":3,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.576895462Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577102221Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577140504Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577278819Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577349466Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577364108Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577426451Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"blockNo":"15","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577512406Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"blockNo":"15","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577594073Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162},"head":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577618449Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"Point","slot":188},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577660881Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.577671136Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.578263774Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a","kind":"BlockPoint","slot":162}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.578290488Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":162}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.57940071Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","targetBlock":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.566280593 UTC to 2025-10-20 19:56:04.580930373 UTC +{"at":"2025-10-20T19:56:04.580352211Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580387848Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580466827Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580470646Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580505817Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580542776Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580570337Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580611451Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","delay":1037246.580472939,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580633012Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580673459Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580699418Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580713277Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580715887Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580735671Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580759383Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","delay":1037225.580679437,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580763613Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"blockNo":"16","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580815479Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580842604Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"blockNo":"16","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580853824Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580871429Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.58089379Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","delay":1037217.580819768,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580918396Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580921188Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179},"head":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580930373Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.580942438Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"Point","slot":222},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.581151868Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.581165192Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.581948619Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709","kind":"BlockPoint","slot":179}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.581975052Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":179}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.582716444Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","targetBlock":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.583346949Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["e8cc9be@351","82758a7@357","9769d5e@362"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.583907745Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.583982488Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584015587Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"SendFetchRequest","length":3,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584058985Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584455605Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584490444Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584617179Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584685419Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584701424Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584744405Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"blockNo":"17","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584825705Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"blockNo":"17","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.58490331Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183},"head":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584925252Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"Point","slot":247},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584928086Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":376},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584966238Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.584975912Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.585331721Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","targetBlock":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586118771Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.58622041Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":24,"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586255033Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586275314Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586306373Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","blockNo":26,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":392},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586935059Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.586976612Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.58711474Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587188639Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587204553Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587272589Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"blockNo":"18","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5873986Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"blockNo":"18","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587501006Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187},"head":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587522661Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"Point","slot":280},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587565847Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587575998Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587777725Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.58786631Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":25,"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587891495Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587908951Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.587934291Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","blockNo":27,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":397},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.588445031Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","targetBlock":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589290397Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd","kind":"BlockPoint","slot":183}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589591319Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589623483Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589737319Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589801216Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589815465Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589840408Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589876227Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"blockNo":"19","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589938454Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":26,"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589947084Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"blockNo":"19","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589965733Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.589985282Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590017612Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","blockNo":28,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":444},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590041884Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188},"head":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590064175Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"Point","slot":304},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590104043Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590112686Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590323361Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","targetBlock":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590362047Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11","kind":"BlockPoint","slot":187}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.590414599Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":187}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.591125442Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736","kind":"BlockPoint","slot":188}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.591155111Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":188}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592360421Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592403317Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592528159Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592593366Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592608039Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.59265115Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"blockNo":"20","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592728871Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"blockNo":"20","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592806103Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222},"head":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592827511Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"Point","slot":325},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592864567Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.592873636Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594144988Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","targetBlock":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594174253Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594199239Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.59428329Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594364862Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594412289Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594455891Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","delay":1037199.594289376,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594523936Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","blockSize":863,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594568743Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.59458664Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594611625Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","delay":1037193.594529935,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":863},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594658772Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.59469676Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594713588Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5947375Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","delay":1037188.594663045,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594762794Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594774257Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.594953034Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595058242Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":27,"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595084864Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595098195Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595119707Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","blockNo":29,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":487},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595239747Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":487},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595242484Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595276553Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595405874Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.5954729Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595487112Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595548035Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"blockNo":"21","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595627422Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"blockNo":"21","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595717897Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247},"head":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595738759Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"Point","slot":333},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595776969Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.595785425Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.596274524Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864","kind":"BlockPoint","slot":222}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.596679324Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","targetBlock":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.580942438 UTC to 2025-10-20 19:56:04.599435323 UTC +{"at":"2025-10-20T19:56:04.596871609Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["a98a7f6@376","b7c2df0@392","521f832@397","12ab6ce@444"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.597686697Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.597911869Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.597942738Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598002247Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9","kind":"BlockPoint","slot":247}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598038646Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":247}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598110222Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598170017Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598184499Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598227442Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"blockNo":"22","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.598296181Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":487},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.599315058Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.599435323Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":28,"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.599460536Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.59967421Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.599699464Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","blockNo":30,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":505},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60031598Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60036253Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600412507Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600640876Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"blockNo":"22","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60075239Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280},"head":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600778879Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"Point","slot":351},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600824529Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600835175Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.600996748Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601096339Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":29,"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601125153Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601152364Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601174647Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","blockNo":31,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":558},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601282929Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":558},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601423229Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","targetBlock":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601732105Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db","kind":"BlockPoint","slot":280}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.601765573Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":280}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602537567Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602571079Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602705307Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602778213Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602793427Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.602840143Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"blockNo":"23","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.603148004Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"blockNo":"23","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60327833Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304},"head":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.603306156Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"Point","slot":357},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.603351808Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.603361389Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.603761254Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","targetBlock":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604262711Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604283385Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60435814Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604431335Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604455825Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604493093Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","delay":1037174.604364112,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604549268Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604590306Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604608069Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604631167Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","delay":1037158.604554596,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604674526Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604711397Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604727362Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604748881Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","delay":1037153.604677975,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604793117Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604830144Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604846278Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604868196Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","delay":1037106.604796939,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604891667Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.604901614Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605197278Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7","kind":"BlockPoint","slot":304}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605232625Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":304}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605580467Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605613414Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605735125Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605800154Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605814169Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60585657Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"blockNo":"24","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.605934325Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"blockNo":"24","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606011194Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325},"head":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606033131Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"Point","slot":362},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606073114Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606081994Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606327734Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","targetBlock":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606692895Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28","kind":"BlockPoint","slot":325}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.606718705Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":325}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607533487Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["2720251@487","0206ad8@505"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60762768Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607658034Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607765768Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607822785Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607836848Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607849581Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607877676Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"blockNo":"25","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.607948872Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"blockNo":"25","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608020919Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333},"head":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.60804168Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"Point","slot":376},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608078784Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608087348Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608818126Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608864608Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"SendFetchRequest","length":2,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.608897936Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609085816Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0","kind":"BlockPoint","slot":333}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609110913Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":333}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.609721716Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","targetBlock":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610220732Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610242585Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61036551Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610430785Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610454378Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610491841Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","delay":1037063.610380675,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610561671Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610600767Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610618063Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610641569Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","delay":1037045.610566848,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610666264Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.610677693Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611584219Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611613352Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611719536Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611773537Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611787523Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611826454Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"blockNo":"26","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611891641Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"blockNo":"26","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.611959512Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351},"head":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61198014Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"Point","slot":392},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.612011904Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.612020991Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.612600334Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","targetBlock":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.612897234Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9","kind":"BlockPoint","slot":351}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.612926325Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":351}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613586558Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613614926Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613719826Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61377682Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613789024Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613828486Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"blockNo":"27","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61389633Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"blockNo":"27","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613960316Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357},"head":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.613979301Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"Point","slot":397},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.614012867Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.614021141Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.614074117Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":558},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.614582226Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","targetBlock":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615087913Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61518461Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":30,"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.599460536 UTC to 2025-10-20 19:56:04.61518461 UTC +{"at":"2025-10-20T19:56:04.615209497Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615438788Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615463056Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","blockNo":32,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":580},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61555279Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615569671Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":580},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615582996Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615694732Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615752591Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615764987Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.615823882Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"blockNo":"28","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616084489Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704","kind":"BlockPoint","slot":357}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616109911Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":357}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616440711Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"blockNo":"28","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616507408Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362},"head":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616527331Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"Point","slot":444},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616559792Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616568447Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616625057Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e","kind":"BlockPoint","slot":362}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616644531Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":362}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.616911372Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","targetBlock":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6178595Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.617889949Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618003483Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618060695Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618074078Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618112716Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"blockNo":"29","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618179851Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"blockNo":"29","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618247236Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376},"head":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.61826696Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"Point","slot":487},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618301853Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618309893Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618651833Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":580},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.618909642Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","targetBlock":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619545907Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c","kind":"BlockPoint","slot":376}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619576426Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":376}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619661403Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619756974Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":31,"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619783062Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619796159Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619816975Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","blockNo":33,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":581},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619902256Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.619931443Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6200397Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620096794Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62010866Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620148103Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"blockNo":"30","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620221393Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"blockNo":"30","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620286465Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392},"head":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620305625Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"Point","slot":505},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620339282Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620347345Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620496843Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["6a17145@558","ef8f495@580"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.620550489Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","targetBlock":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62076181Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.621475967Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.621544806Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":32,"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.621563325Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.621573658Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62158998Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","blockNo":34,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":588},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.622515098Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.622567808Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":33,"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.622584607Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.622594191Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.622607934Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","blockNo":35,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":602},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623469534Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623521535Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":34,"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623531419Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623536815Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623547333Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623560474Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","blockNo":36,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":707},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62356235Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623632958Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":707},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623675925Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623736262Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623751314Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623833319Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3","kind":"BlockPoint","slot":392}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.623863174Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":392}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.624219913Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.624238502Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":397}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.624597988Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62464544Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"SendFetchRequest","length":2,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.624685176Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625812228Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.625834467Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626095107Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626165331Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626190026Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626227562Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","delay":1036992.626104543,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626285574Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626324416Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626342506Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626377225Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","delay":1036970.626290673,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626402434Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626414273Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62672366Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62674786Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626780657Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"blockNo":"31","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626871578Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"blockNo":"31","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626938918Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995","kind":"BlockPoint","slot":397},"head":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.626963132Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"Point","slot":558},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.627007187Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.627016014Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.627067825Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","targetBlock":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62811514Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628150273Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628279932Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.615209497 UTC to 2025-10-20 19:56:04.630745353 UTC +{"at":"2025-10-20T19:56:04.628394803Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628408958Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628452388Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"blockNo":"32","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628527997Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"blockNo":"32","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628603089Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444},"head":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.62862458Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"Point","slot":580},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628662739Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628672465Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628715385Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","targetBlock":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.628786338Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":707},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.629700969Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.629731112Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.629843603Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.629903364Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.629919532Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630037245Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173","kind":"BlockPoint","slot":444}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630069835Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":444}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630589593Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630684333Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":35,"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630710899Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630724692Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.630745353Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","blockNo":37,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":710},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.631016527Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.631257361Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":487}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.631679925Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["a1bd89b@581","d83ade2@588","a832dca@602","435973c@707"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.631980363Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632047156Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632661919Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632688586Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"SendFetchRequest","length":4,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632718163Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632718032Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":36,"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632761939Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632781723Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.632809537Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","blockNo":38,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":728},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633614879Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633689161Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":37,"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633707007Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633717386Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.633732618Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","blockNo":39,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":740},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634360126Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634389271Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634426833Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634457005Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634478564Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":38,"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634493229Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634503091Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634516232Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","blockNo":40,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":746},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634516998Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634540856Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634576509Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","delay":1036969.634463042,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634626271Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634663311Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634680691Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.634702131Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","delay":1036962.634631017,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635076443Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.63508784Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635112074Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"blockNo":"33","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635178172Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635195819Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"blockNo":"33","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635227387Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":39,"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635242697Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635252429Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635257127Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336","kind":"BlockPoint","slot":487},"head":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635265309Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","blockNo":41,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":756},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635278578Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"Point","slot":581},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635319471Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6353277Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635921331Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635974068Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":40,"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635988946Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.635998203Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.636011281Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","blockNo":42,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":780},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.636065806Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":780},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.636652127Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","targetBlock":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.63743728Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637518822Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637545567Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637584938Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","delay":1036948.637449814,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637650622Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637690352Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637707849Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637731224Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","delay":1036843.637655291,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637755592Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.637765507Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6381065Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638144128Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638270683Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638338831Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638352862Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638408523Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"blockNo":"34","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638495762Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"blockNo":"34","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638573866Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505},"head":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638594966Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"Point","slot":588},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.638634393Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.63864255Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.639072793Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57","kind":"BlockPoint","slot":505}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.639099066Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":505}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.639376508Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","targetBlock":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640321114Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640354346Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64047685Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640538126Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640552069Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640591866Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"blockNo":"35","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640665434Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"blockNo":"35","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640737429Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558},"head":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640759018Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"Point","slot":602},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640795121Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.640803713Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.641824515Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","targetBlock":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.642694078Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab","kind":"BlockPoint","slot":558}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.642727523Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":558}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.642784899Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["0dccbe6@710","e4e8468@728","120f49d@740","0e7f6e6@746","adc0a33@756"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643196595Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643444875Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643477595Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643579325Z","ns":"ChainDB.AddBlockEvent.AddedToCurrentChain","data":{"events":[{"epochNo":"EpochNo 2","kind":"ShelleyUpdatedProtocolUpdates","updates":"SNothing"}],"kind":"AddedToCurrentChain","newTipSelectView":{"chainLength":35,"issueNo":0,"issuerHash":"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc","kind":"PraosChainSelectView","slotNo":602,"tieBreakVRF":"713fe8793dfe40bb9ba9315f6f1aca910bd7c9fdf8e74adc2b02494d9c37b6bc387ff810fc425fa6c26142dd07b1fc09c5ff17814bcda5532a1835f66fe260cc"},"newtip":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","oldTipSelectView":{"chainLength":34,"issueNo":0,"issuerHash":"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7","kind":"PraosChainSelectView","slotNo":588,"tieBreakVRF":"2c378d8710efaab90d72652d042886ef8d1d4b1365d016c30267cebd038f2a77c1b6bcb7fd121ad12840541641b1f4c3ca21985b8847eebceb927c82be65018d"}},"sev":"Notice","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643669307Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64373452Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64374827Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643790217Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"blockNo":"36","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643871838Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"blockNo":"36","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.643944387Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580},"head":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64396485Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"Point","slot":707},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644001271Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644010038Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644224356Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":780},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644219271Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644263492Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"SendFetchRequest","length":5,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.644295931Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645190377Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645249099Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":41,"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645271701Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645281871Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645298761Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","blockNo":43,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":795},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645388053Z","ns":"ChainSync.Client.WaitingBeyondForecastHorizon","data":{"kind":"WaitingBeyondForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":795},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.645687164Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","targetBlock":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646450318Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb","kind":"BlockPoint","slot":580}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646487185Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":580}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646649918Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646682723Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646790377Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646848543Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.646863105Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.647158394Z","ns":"ChainSync.Client.AccessingForecastHorizon","data":{"kind":"AccessingForecastHorizon","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slotNo":795},"sev":"Debug","thread":"71","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.631016527 UTC to 2025-10-20 19:56:04.648107513 UTC +{"at":"2025-10-20T19:56:04.647999885Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648058975Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":42,"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648080199Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648090738Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648107513Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","blockNo":44,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":809},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648189879Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648501661Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":581}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648698972Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648721292Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648798701Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64887241Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648897786Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6489344Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","delay":1036840.648804511,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.648998979Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649040769Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649057488Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64908237Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","delay":1036822.649004446,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649131622Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64916715Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649182855Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649203852Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","delay":1036810.649135769,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649244483Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649279642Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649295389Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649315696Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","delay":1036804.649248407,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649355923Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64940283Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649417901Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649437411Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","delay":1036794.649359646,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649458404Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649468051Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649512877Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64956799Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":43,"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649586208Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649596399Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649626014Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.64964118Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649660235Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"fallingEdge":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"ChainSelStarvation"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649673513Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649697089Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"blockNo":"37","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649780308Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"blockNo":"37","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649839923Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9","kind":"BlockPoint","slot":581},"head":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649860338Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"Point","slot":710},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649902833Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.649913457Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.650031323Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","targetBlock":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.651703536Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65173398Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.651849819Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.651913077Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.651925949Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.651965696Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"blockNo":"38","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.652049462Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"blockNo":"38","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65212134Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588},"head":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.652141293Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"Point","slot":728},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.652177697Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65218622Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.652227017Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","targetBlock":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6530714Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653133447Z","ns":"ChainSync.Remote.Receive.RollForward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollForward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"70","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653382554Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653428489Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653575208Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653650968Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65366481Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653724768Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"blockNo":"39","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653806732Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"blockNo":"39","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653898824Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602},"head":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653919067Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"Point","slot":740},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.653957693Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65396576Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6543909Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88","kind":"BlockPoint","slot":588}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.654414781Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":588}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.654805979Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","blockNo":45,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":810},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.655624692Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b","kind":"BlockPoint","slot":602}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.655647669Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":602}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.655705864Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","targetBlock":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.656296761Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65636228Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":44,"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.656395189Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65640673Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.656424538Z","ns":"ChainSync.Client.DownloadedHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","blockNo":46,"kind":"DownloadedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"slot":829},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.656967533Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.656999874Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65710726Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657166788Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657180218Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657219862Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"blockNo":"40","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657293391Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"blockNo":"40","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657377059Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707},"head":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657397928Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"Point","slot":746},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657435979Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657444526Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657581984Z","ns":"ChainSync.Client.ValidatedHeader","data":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"ValidatedHeader","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.65767678Z","ns":"ChainSync.Client.GaveLoPToken","data":{"blockNo":45,"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"TraceGaveLoPToken","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tokenAdded":true},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657700818Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657713012Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657744497Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.657827279Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":["751da61@780","0e45f81@795","d4b3efb@809","de8f9b6@810","4135510@829"],"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.658276375Z","ns":"BlockFetch.Client.AddedFetchRequest","data":{"kind":"AddedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.658644178Z","ns":"BlockFetch.Client.AcknowledgedFetchRequest","data":{"kind":"AcknowledgedFetchRequest","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.658675635Z","ns":"BlockFetch.Client.SendFetchRequest","data":{"head":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"SendFetchRequest","length":5,"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.658710492Z","ns":"BlockFetch.Remote.Send.RequestRange","data":{"kind":"Send","msg":{"agency":"SingBFIdle","kind":"MsgRequestRange"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"65","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.658913381Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","targetBlock":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66014045Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720","kind":"BlockPoint","slot":707}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.660177786Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":707}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.660395523Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.660434257Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66056824Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661158439Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661185403Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":710}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661251917Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661265608Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661290091Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"blockNo":"41","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661356194Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"blockNo":"41","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661432203Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7","kind":"BlockPoint","slot":710},"head":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661455915Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"Point","slot":756},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661497484Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661506614Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.661549376Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","targetBlock":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662196302Z","ns":"BlockFetch.Remote.Receive.StartBatch","data":{"kind":"Recv","msg":{"agency":"SingBFBusy","kind":"MsgStartBatch"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662218771Z","ns":"BlockFetch.Client.StartedFetchBatch","data":{"kind":"StartedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662289883Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662349439Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6623801Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"AddedBlockToQueue","queueSize":1},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662416652Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","delay":1036770.662295516,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.648189879 UTC to 2025-10-20 19:56:04.66263638 UTC +{"at":"2025-10-20T19:56:04.662468007Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662505254Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662522528Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"AddedBlockToQueue","queueSize":2},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662544349Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","delay":1036755.662473073,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.6625854Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662620235Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66263638Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"AddedBlockToQueue","queueSize":3},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662657297Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","delay":1036741.662589182,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662820433Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662860614Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662879891Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"AddedBlockToQueue","queueSize":4},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66290291Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","delay":1036740.662825653,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662943943Z","ns":"BlockFetch.Remote.Receive.Block","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","blockHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","blockSize":864,"kind":"MsgBlock","txIds":[]},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662977803Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"AddedBlockToQueue","risingEdge":true},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.662993056Z","ns":"ChainDB.AddBlockEvent.AddedBlockToQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"AddedBlockToQueue","queueSize":5},"sev":"Debug","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663014013Z","ns":"BlockFetch.Client.CompletedBlockFetch","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","delay":1036721.6629479,"kind":"CompletedBlockFetch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"size":864},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663036361Z","ns":"BlockFetch.Remote.Receive.BatchDone","data":{"kind":"Recv","msg":{"agency":"SingBFStreaming","kind":"MsgBatchDone"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663046683Z","ns":"BlockFetch.Client.CompletedFetchBatch","data":{"kind":"CompletedFetchBatch","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"64","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663215759Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66324588Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663357564Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663426556Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663440391Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663479245Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"blockNo":"42","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66353989Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"71","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663605969Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"blockNo":"42","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663674249Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728},"head":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663693571Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"Point","slot":780},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663728445Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.663737164Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.664343738Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf","kind":"BlockPoint","slot":728}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.664378212Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":728}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.664652641Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","targetBlock":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665610319Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.66564477Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665751067Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665808332Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665822168Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665862586Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"blockNo":"43","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.665933825Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"blockNo":"43","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666004904Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740},"head":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666025026Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"Point","slot":795},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666062181Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666071999Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666491998Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e","kind":"BlockPoint","slot":740}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666516929Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":740}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.666670092Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","targetBlock":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.667604984Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.667636911Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.667746412Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668148801Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668171968Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":746}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668337269Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668353196Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668386567Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"blockNo":"44","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668448678Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"blockNo":"44","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668504304Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778","kind":"BlockPoint","slot":746},"head":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668525824Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"Point","slot":809},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668561165Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668570035Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.668610167Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","targetBlock":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669004733Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineAlreadyFetched"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669621912Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669656345Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"BlockPoint","slot":809},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669775759Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669837637Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669851066Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669892884Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"blockNo":"45","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.669969827Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"blockNo":"45","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670041238Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756},"head":{"headerHash":"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07","kind":"BlockPoint","slot":809}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670061026Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"Point","slot":810},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670099558Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670108129Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.67042727Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3","kind":"BlockPoint","slot":756}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670449607Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":756}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.670663864Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","targetBlock":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.671603915Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.671636732Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"BlockPoint","slot":810},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.671748384Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672280387Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672305172Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":780}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672480474Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672495621Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"TraceAddBlockEvent.PoppedBlockFromQueue"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672517479Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"blockNo":"46","kind":"AddedBlockToVolatileDB","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672579003Z","ns":"ChainDB.AddBlockEvent.AddedBlockToVolatileDB","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"blockNo":"46","kind":"AddedBlockToVolatileDB"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672634192Z","ns":"ChainDB.AddBlockEvent.ChainSelectionLoEDebug","data":{"curChain":{"anchor":{"headerHash":"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98","kind":"BlockPoint","slot":780},"head":{"headerHash":"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8","kind":"BlockPoint","slot":810}},"kind":"ChainSelectionLoEDebug","loeFrag":"LoE is disabled"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672656181Z","ns":"ChainDB.AddBlockEvent.TryAddToCurrentChain","data":{"block":{"hash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"Point","slot":829},"kind":"TryAddToCurrentChain"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672689954Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"SetTentativeHeader","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672698298Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"SetTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.672736905Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.UpdateLedgerDb","data":{"currentBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"UpdateLedgerDbTraceEvent.StartedPushingBlockToTheLedgerDb","startingBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","targetBlock":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.673678572Z","ns":"ChainDB.AddBlockEvent.AddBlockValidation.ValidCandidate","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"ValidCandidate"},"sev":"Info","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.673710454Z","ns":"ChainDB.AddBlockEvent.ChangingSelection","data":{"block":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829},"kind":"TraceAddBlockEvent.ChangingSelection"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.673823622Z","ns":"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader","data":{"block":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829","kind":"OutdatedTentativeHeader"},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.673878408Z","ns":"ChainDB.AddBlockEvent.PoppedBlockFromQueue","data":{"kind":"TraceAddBlockEvent.PoppedBlockFromQueue","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.673893781Z","ns":"ChainDB.ChainSelStarvationEvent","data":{"kind":"ChainSelStarvation","risingEdge":true},"sev":"Debug","thread":"18","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.674296546Z","ns":"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB","data":{"kind":"CopiedBlockToImmutableDB","slot":{"headerHash":"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a","kind":"BlockPoint","slot":795}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.674318165Z","ns":"ChainDB.GCEvent.ScheduledGC","data":{"kind":"ScheduledGC","slot":{"kind":"SlotNo","slot":795}},"sev":"Debug","thread":"22","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.674514354Z","ns":"Consensus.GSM.EnterCaughtUp","data":{"currentSelection":{"kind":"Tip","tipBlockNo":46,"tipHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","tipSlotNo":829},"kind":"GsmEventEnterCaughtUp","peerNumber":1},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T19:56:04.679573914Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:14.690798676Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:24.69220835Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:34.693149996Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:44.694475008Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:54.69560935Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:56:59.476839712Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:56:59.476688754 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:57:04.697174978Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:14.529885161Z","ns":"ChainDB.GCEvent.PerformedGC","data":{"kind":"PerformedGC","slot":{"kind":"SlotNo","slot":795}},"sev":"Debug","thread":"20","host":"pamperito-III"} +{"at":"2025-10-20T19:57:14.698230804Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:24.699102963Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:34.700534417Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:44.701682851Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:54.70307488Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:57:59.478721353Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:57:59.478577223 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:58:04.704038483Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:14.705162466Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:24.706646697Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:34.707074063Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:44.708287916Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:46.313014959Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"56","host":"pamperito-III"} +{"at":"2025-10-20T19:58:46.313164715Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:46.313215295Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:58:46.314901524Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:46.315493546Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",11.92883875197]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.319495907Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.319798126Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.31993Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.32091984Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.32094037Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321003592Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321016869Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.32103975Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321625374Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321641968Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321705296Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.321713953Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"107","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:56:04.662657297 UTC to 2025-10-20 19:58:56.321713953 UTC +{"at":"2025-10-20T19:58:56.321731455Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.323584762Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"107","host":"pamperito-III"} +{"at":"2025-10-20T19:58:56.329747619Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:58:59.480477659Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:58:59.480366115 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T19:59:06.340993045Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:16.341975881Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:26.342702934Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:36.343829751Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:46.344938738Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:56.34639242Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T19:59:59.482417661Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 19:59:59.482241959 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:00:06.347548794Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:16.348802738Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:26.349886269Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:36.351295811Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:46.351794307Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:56.352744818Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:00:59.483705777Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:00:59.483567388 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:01:06.354085959Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:16.355116919Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:26.356731101Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:36.358537017Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:46.359740865Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.571777676Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.57206442Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.572240788Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"92","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.573053744Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:49.573691064Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",12.276680492063]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.48485153Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:01:59.484697035 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.576955065Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.577142189Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.577385708Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.578346787Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.578393672Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.57849688Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.578515333Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.578545319Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.579384506Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.579406872Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.579479976Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.579491344Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.579511457Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.58021947Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"130","host":"pamperito-III"} +{"at":"2025-10-20T20:01:59.588316577Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:09.599859267Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:19.600659337Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:29.601912796Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:39.602609754Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:49.60379864Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:02:59.485853688Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:02:59.485712228 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:02:59.605156417Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:09.606602981Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:19.607517781Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:29.608734267Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:39.609930014Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:49.61094295Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:03:59.487454673Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:03:59.487290563 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:03:59.611773453Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:09.612503387Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:19.613391512Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:29.614496234Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:39.616519834Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:49.617726352Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:53.83874222Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:53.839030121Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:04:53.839174438Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"115","host":"pamperito-III"} +{"at":"2025-10-20T20:04:53.839745772Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:04:53.839918555Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",12.847410613463]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:04:59.488126415Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:04:59.488021005 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.843311688Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.843414906Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.843899845Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.844789344Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.844817086Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.844908257Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.844924617Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.8449483Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.845924994Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.845964478Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.84608248Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.846099986Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.846133253Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.846934011Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"152","host":"pamperito-III"} +{"at":"2025-10-20T20:05:03.85417324Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:13.865167697Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:23.865949196Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:33.86695715Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:43.867682044Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:53.868723426Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:05:59.474966232Z","ns":"ChainDB.ImmDbEvent.CacheEvent.PastChunkExpired","data":{"chunkNos":"[\"0\",\"16\",\"24\",\"25\",\"17\",\"20\",\"22\",\"23\",\"21\",\"18\",\"19\",\"1\",\"8\",\"12\",\"14\",\"15\",\"13\",\"9\",\"10\",\"11\",\"2\",\"4\",\"6\",\"7\",\"5\",\"3\"]","kind":"TracePastChunksExpired","noPastChunks":"0"},"sev":"Debug","thread":"16","host":"pamperito-III"} +{"at":"2025-10-20T20:05:59.489104372Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:05:59.488981214 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:06:03.870012834Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:13.871335752Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:23.872022384Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:33.873193536Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:43.873923362Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:53.875169894Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:06:59.490683398Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:06:59.49056054 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:07:03.876524256Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:13.878332034Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:23.880294142Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:33.881301998Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:43.882732321Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:53.884251194Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:07:59.491505622Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:07:59.491321358 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:08:03.886199149Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:13.88756317Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:22.907212991Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"137","host":"pamperito-III"} +{"at":"2025-10-20T20:08:22.907238137Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:22.907436136Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:08:22.908070887Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:22.90830923Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",11.625430270839]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.912163383Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.912300134Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.912578667Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.913560719Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.913581947Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.913650968Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.913667643Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.913694687Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.914402903Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.914422306Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.91450159Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.914511418Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.914532044Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.915225445Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"173","host":"pamperito-III"} +{"at":"2025-10-20T20:08:32.923151349Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:42.934763006Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 19:58:56.321731455 UTC to 2025-10-20 20:08:42.934763006 UTC +{"at":"2025-10-20T20:08:52.935962859Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:08:59.493412198Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:08:59.493222219 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:09:02.937569409Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:12.938239564Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:22.939577478Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:32.940700893Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:42.941414912Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:52.942023371Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:09:59.495715084Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:09:59.495577799 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:10:02.94341259Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:12.944451881Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:22.945800388Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:32.946958748Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:42.947785967Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:52.948975384Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:10:59.497071587Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:10:59.496971699 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:11:02.949888548Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:06.524927001Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:06.525180734Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"158","host":"pamperito-III"} +{"at":"2025-10-20T20:11:06.525515841Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:11:06.526419497Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:06.527065945Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",11.890617863019]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.531457977Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.531897285Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.533677717Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.533714503Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.533815617Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.53383586Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.533871412Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.534219306Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.535040091Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.535078958Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.535194928Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.535208246Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.535236857Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:16.536262873Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"195","host":"pamperito-III"} +{"at":"2025-10-20T20:11:26.543072233Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:32.911481567Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":5,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:11:36.543956086Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:46.544971649Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:56.545781616Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:11:59.49861002Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:11:59.498520177 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:12:06.546395367Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:16.547280534Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:26.548412905Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:32.911959988Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActiveBigLedgerPeers","counter":0,"duration":60.000664366,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:12:32.912294936Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:12:36.549876062Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:46.551323386Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:56.552724882Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:12:59.499981001Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:12:59.499821332 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:13:06.554709344Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:16.555707574Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:26.557476553Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:36.559271724Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:46.560679496Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:52.913642461Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownBigLedgerPeers","counter":0,"duration":80.001421976,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:13:52.913872882Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:13:56.561725831Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:13:59.501693024Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:13:59.501320719 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:14:06.563120551Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:16.564386912Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:26.565129303Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:36.566123434Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:46.567230403Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:52.915501864Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedBigLedgerPeers","counter":0,"duration":60.001736221,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:14:52.915764778Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":15,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:14:56.568500182Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:14:59.503066437Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:14:59.502926349 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:15:06.569489141Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:16.570550104Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:26.571496878Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:36.070721047Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"180","host":"pamperito-III"} +{"at":"2025-10-20T20:15:36.070967601Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:36.071272832Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:15:36.072087855Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:36.072718321Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",12.915231637639]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.076534147Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.076771442Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.077818001Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.07786103Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.077990875Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.078022312Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.078072736Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.078401305Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.079005459Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.079043571Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.079179276Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.079203875Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.079247138Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:46.080109783Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"218","host":"pamperito-III"} +{"at":"2025-10-20T20:15:52.91670278Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActivePeers","counter":0,"duration":60.000986731,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:15:52.917230934Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":40,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:15:56.088668104Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:15:59.504279677Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:15:59.504142978 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:16:04.676006756Z","ns":"Consensus.GSM.LeaveCaughtUp","data":{"age":"Already","currentSelection":{"kind":"Tip","tipBlockNo":46,"tipHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","tipSlotNo":829},"kind":"GsmEventLeaveCaughtUp"},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T20:16:04.676049565Z","ns":"Consensus.GSM.GsmEventPreSyncingToSyncing","data":{"kind":"GsmEventPreSyncingToSyncing"},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T20:16:04.676355941Z","ns":"Consensus.GSM.EnterCaughtUp","data":{"currentSelection":{"kind":"Tip","tipBlockNo":46,"tipHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","tipSlotNo":829},"kind":"GsmEventEnterCaughtUp","peerNumber":1},"sev":"Info","thread":"28","host":"pamperito-III"} +{"at":"2025-10-20T20:16:06.089997687Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:16.091019608Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:26.092001581Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:36.093264202Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:46.094632904Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:56.096442708Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:16:59.505055449Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:16:59.504963351 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:17:06.098247442Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:12.918664741Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownPeers","counter":0,"duration":80.00166902,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:17:12.919034318Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:17:16.099762956Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:26.101847095Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:36.103569696Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:46.105612668Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:56.10756312Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:17:59.506306752Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:17:59.506208377 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:18:06.108841475Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:12.919895036Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedPeers","counter":0,"duration":60.001115235,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:18:16.10974522Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:26.111677981Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:36.113514846Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:46.115651229Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:56.116865264Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:18:59.507838786Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:18:59.507676652 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:19:06.118605103Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:16.120533017Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:26.122548334Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:36.124507581Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:46.125526538Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:19:56.126832468Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 20:08:52.935962859 UTC to 2025-10-20 20:19:56.126832468 UTC +{"at":"2025-10-20T20:19:59.510168317Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:19:59.510006153 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:20:06.128563022Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:07.4196945Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"203","host":"pamperito-III"} +{"at":"2025-10-20T20:20:07.419898339Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:07.420298491Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:20:07.421250987Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:07.422042996Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",11.559248196891]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.42646974Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.426934227Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.427023059Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.428518013Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.428559398Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.428708497Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.428735103Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.428780483Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.429872777Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.429919754Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.430048927Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.430065318Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.430100451Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.43173929Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"241","host":"pamperito-III"} +{"at":"2025-10-20T20:20:17.436944797Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:27.449041307Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:37.449842403Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:47.451035764Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:57.452735476Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:20:59.512086274Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:20:59.511950275 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:21:07.453667903Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:17.454747698Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:27.456185716Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:37.457143792Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:47.457793204Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:57.458982119Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:21:59.513690554Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:21:59.51359489 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:22:07.459798557Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:17.460780345Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:27.462758047Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:37.465142621Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:47.467141473Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:57.468878667Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:22:59.51493813Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:22:59.514804265 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:23:07.470218848Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:17.471524829Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:27.47284369Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:37.473887976Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:47.475853587Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:57.477266833Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:23:59.516735698Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:23:59.516620249 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:24:03.772148926Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:03.77226045Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"226","host":"pamperito-III"} +{"at":"2025-10-20T20:24:03.772918086Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:24:03.773475908Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:03.77380748Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",11.530502595896]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.776867528Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.777114814Z","ns":"ChainSync.Remote.Send.FindIntersect","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgFindIntersect"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.777982979Z","ns":"ChainSync.Remote.Receive.IntersectFound","data":{"kind":"Recv","msg":{"agency":"SingIntersect","kind":"MsgIntersectFound"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.778011846Z","ns":"ChainSync.Client.FoundIntersection","data":{"kind":"FoundIntersection","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.778096916Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.778117214Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.778151351Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.778428003Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.779216993Z","ns":"ChainSync.Remote.Receive.RollBackward","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgRollBackward"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.779250359Z","ns":"ChainSync.Client.RolledBack","data":{"kind":"RolledBack","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"tip":{"headerHash":"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553","kind":"BlockPoint","slot":829}},"sev":"Notice","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.779340199Z","ns":"ChainSync.Client.JumpingWaitingForNextInstruction","data":{"kind":"TraceJumpingWaitingForNextInstruction","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.779351292Z","ns":"ChainSync.Client.JumpingInstructionIs","data":{"instr":{"kind":"RunNormally"},"kind":"TraceJumpingInstructionIs","peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Debug","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.779389529Z","ns":"ChainSync.Remote.Send.RequestNext","data":{"kind":"Send","msg":{"agency":"SingIdle","kind":"MsgRequestNext"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:13.780058881Z","ns":"ChainSync.Remote.Receive.AwaitReply","data":{"kind":"Recv","msg":{"agency":"SingNext SingCanAwait","kind":"MsgAwaitReply"},"peer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"}},"sev":"Info","thread":"264","host":"pamperito-III"} +{"at":"2025-10-20T20:24:23.789264426Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:33.790176397Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:43.79162612Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:53.793019795Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:24:59.517856343Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:24:59.517723389 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:25:03.794442804Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:13.795840927Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:23.79776388Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:33.799256638Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:43.801123459Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:53.803478679Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:25:59.519176094Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:25:59.519017046 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:26:03.805728185Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:13.807803011Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:23.809861855Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:33.811186645Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:43.81320712Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:53.814743336Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:26:59.520401304Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:26:59.520291722 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:27:03.815896837Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:13.817722873Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[{"decision":{"declined":"FetchDeclineChainNotPlausible"},"peer":{"localAddress":{"address":"127.0.0.1","port":"3003"},"remoteAddress":{"address":"127.0.0.1","port":"3002"}}}],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:14.601983113Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:14.602196236Z","ns":"Net.Mux.Remote.ExceptionExit","data":{"bearer":{"connectionId":"127.0.0.1:3003 127.0.0.1:3002"},"event":{"exception":"ExceededTimeLimit (ChainSync (Header (HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) (Tip HardForkBlock (': * ByronBlock (': * (ShelleyBlock (TPraos StandardCrypto) ShelleyEra) (': * (ShelleyBlock (TPraos StandardCrypto) AllegraEra) (': * (ShelleyBlock (TPraos StandardCrypto) MaryEra) (': * (ShelleyBlock (TPraos StandardCrypto) AlonzoEra) (': * (ShelleyBlock (Praos StandardCrypto) BabbageEra) (': * (ShelleyBlock (Praos StandardCrypto) ConwayEra) ('[] *)))))))))) ServerHasAgency (SingNext SingMustReply)","kind":"Mux.TraceExceptionExit","miniProtocolDir":"InitiatorDir","miniProtocolNum":"MiniProtocolNum 2","msg":"Miniprotocol terminated with exception"},"kind":"Mux.Trace"},"sev":"Notice","thread":"249","host":"pamperito-III"} +{"at":"2025-10-20T20:27:14.603010359Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCooling",null]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:27:14.603604039Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:14.604195479Z","ns":"Net.PeerSelection.Selection.DemoteLocalAsynchronous","data":{"kind":"DemoteLocalAsynchronous","state":[[{"address":"127.0.0.1","port":"3002"},["PeerCold",12.9645425218]]]},"sev":"Warning","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:27:24.605269928Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"270","host":"pamperito-III"} +{"at":"2025-10-20T20:27:24.613826024Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:34.615234618Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:35.29042314Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"271","host":"pamperito-III"} +{"at":"2025-10-20T20:27:44.616641606Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:54.617821173Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:27:56.922257206Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"272","host":"pamperito-III"} +{"at":"2025-10-20T20:27:59.520916878Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:27:59.520814456 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:28:04.619441616Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:09.037743102Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActiveBigLedgerPeers","counter":0,"duration":60.00079473,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:28:09.038094785Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:28:14.621172286Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:24.62204348Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:34.622772009Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:36.095622119Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"273","host":"pamperito-III"} +{"at":"2025-10-20T20:28:44.623719576Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:54.62528374Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:28:59.521775316Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:28:59.521620475 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:29:04.626951895Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:14.628612586Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:24.630261856Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:29.038757057Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownBigLedgerPeers","counter":0,"duration":80.000719793,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:29:29.03913076Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":9,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:29:34.631578288Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:44.632681871Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:54.63368554Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:29:55.91982968Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"275","host":"pamperito-III"} +{"at":"2025-10-20T20:29:59.523050164Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:29:59.522886104 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:30:04.634658963Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:14.635363515Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:24.636781243Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:29.040560112Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedBigLedgerPeers","counter":0,"duration":60.00166967,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:30:34.63772563Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:44.63864803Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:30:54.63934436Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +TraceObject queue overflowed. Dropped 128 messages from 2025-10-20 20:19:59.510168317 UTC to 2025-10-20 20:30:54.63934436 UTC +{"at":"2025-10-20T20:30:59.524261961Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:30:59.524106101 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:31:04.640907148Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:14.642029345Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:24.64355726Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:29.042569626Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedActivePeers","counter":0,"duration":60.001708936,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:31:29.042945822Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:31:34.644884243Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:44.647420345Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:54.649517975Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:31:59.526062682Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:31:59.525912902 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:32:04.650722816Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:14.65226911Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:24.653881173Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:34.149302292Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"278","host":"pamperito-III"} +{"at":"2025-10-20T20:32:34.65534232Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:44.657557885Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:49.043715402Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedKnownPeers","counter":0,"duration":80.000835654,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:32:49.044071718Z","ns":"Net.PeerSelection.Selection.TargetsChanged","data":{"current":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":3,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60},"kind":"TargetsChanged","previous":{"kind":"PeerSelectionTargets","targetActiveBigLedgerPeers":1,"targetActivePeers":2,"targetEstablishedBigLedgerPeers":10,"targetEstablishedPeers":2,"targetKnownBigLedgerPeers":15,"targetKnownPeers":150,"targetRootPeers":60}},"sev":"Notice","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:32:54.66007783Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:32:59.526976214Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:32:59.526821597 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:33:04.662421163Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:14.663980982Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:24.66612317Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:34.668057292Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:44.670346284Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:49.044836964Z","ns":"Net.PeerSelection.Selection.ChurnTimeout","data":{"action":"IncreasedEstablishedPeers","counter":0,"duration":60.000989626,"kind":"ChurnTimeout"},"sev":"Notice","thread":"51","host":"pamperito-III"} +{"at":"2025-10-20T20:33:54.671971464Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:33:59.527951808Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:33:59.527799094 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:34:04.673623365Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:14.675640555Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:24.677670382Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:34.678753364Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:44.679796466Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:54.681756656Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:34:59.529526376Z","ns":"BlockchainTime.CurrentSlotUnknown","data":{"kind":"CurrentSlotUnknown","time":"2025-10-20 20:34:59.529357234 UTC"},"sev":"Warning","thread":"24","host":"pamperito-III"} +{"at":"2025-10-20T20:35:04.683688126Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:13.324925219Z","ns":"Net.PeerSelection.Actions.ConnectionError","data":{"error":"Network.Socket.connect: : unsupported operation (Cannot assign requested address)","kind":"AcquireConnectionError"},"sev":"Error","thread":"281","host":"pamperito-III"} +{"at":"2025-10-20T20:35:14.685121174Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:24.686474577Z","ns":"BlockFetch.Decision.PeersFetch","data":{"decisions":[],"kind":"PeerFetch"},"sev":"Debug","thread":"32","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300265114Z","ns":"Net.Server.Remote.Error","data":{"kind":"ServerError","reason":"AsyncCancelled"},"sev":"Critical","thread":"50","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.30026601Z","ns":"Net.Server.Local.Error","data":{"kind":"ServerError","reason":"AsyncCancelled"},"sev":"Critical","thread":"46","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300323737Z","ns":"Net.Server.Remote.Stopped","data":{"kind":"ServerStopped"},"sev":"Notice","thread":"36","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.300398917Z","ns":"Net.PeerSelection.Selection.OutboundGovernorCriticalFailure","data":{"kind":"OutboundGovernorCriticalFailure","reason":"AsyncCancelled"},"sev":"Error","thread":"49","host":"pamperito-III"} +{"at":"2025-10-20T20:35:30.30065111Z","ns":"Net.Server.Local.Stopped","data":{"kind":"ServerStopped"},"sev":"Notice","thread":"37","host":"pamperito-III"} From cbb0ae3d47539760ed0dc32479b1d290cdc2ef9b Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Tue, 21 Oct 2025 18:08:05 +0200 Subject: [PATCH 035/119] Add the IPython notebook for interactive analysis Run `jupyter-lab` in the provided Nix shell --- flake.lock | 18 +++- flake.nix | 7 +- scripts/leios-demo/build.nix | 4 +- scripts/leios-demo/demo_analysis.ipynb | 110 +++++++++++++++++++++++++ scripts/leios-demo/requirements.txt | 2 + 5 files changed, 138 insertions(+), 3 deletions(-) create mode 100644 scripts/leios-demo/demo_analysis.ipynb diff --git a/flake.lock b/flake.lock index 6997cbaa1f..b7205cf289 100644 --- a/flake.lock +++ b/flake.lock @@ -768,6 +768,21 @@ "type": "github" } }, + "nixpkgs-unstable_2": { + "locked": { + "lastModified": 1761061156, + "narHash": "sha256-vACmgVPMmsxeUJQ4KSZdHCEAYPPWDvfvvb3o4jImQ0Q=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "c0df53a387e55cc22d9b444c45597ef42f6606a5", + "type": "github" + }, + "original": { + "owner": "NixOS", + "repo": "nixpkgs", + "type": "github" + } + }, "old-ghc-nix": { "flake": false, "locked": { @@ -799,7 +814,8 @@ "nixpkgs": [ "haskellNix", "nixpkgs-unstable" - ] + ], + "nixpkgs-unstable": "nixpkgs-unstable_2" } }, "secp256k1": { diff --git a/flake.nix b/flake.nix index 9dae47b55d..28f9d4e1b7 100644 --- a/flake.nix +++ b/flake.nix @@ -41,6 +41,9 @@ url = "github:phadej/gentle-introduction"; flake = false; }; + + nixpkgs-unstable.url = "github:NixOS/nixpkgs"; + }; outputs = inputs: let @@ -69,7 +72,9 @@ ]; }; hydraJobs = import ./nix/ci.nix { inherit inputs pkgs; }; - leiosDemo = import ./scripts/leios-demo/build.nix { inherit inputs pkgs; }; + leiosDemo = import ./scripts/leios-demo/build.nix { inherit inputs; + pkgs = import inputs.nixpkgs-unstable {inherit system;}; + }; in { devShells = rec { diff --git a/scripts/leios-demo/build.nix b/scripts/leios-demo/build.nix index 882d4f68ee..30647deab9 100644 --- a/scripts/leios-demo/build.nix +++ b/scripts/leios-demo/build.nix @@ -6,14 +6,16 @@ name = "leios-demo"; buildInputs = with pkgs; with python3Packages; [ - python3 + python ipython pandas + altair pip virtualenv python-lsp-server jupyterlab black + itables nixpkgs-fmt nil diff --git a/scripts/leios-demo/demo_analysis.ipynb b/scripts/leios-demo/demo_analysis.ipynb new file mode 100644 index 0000000000..40ebd6126f --- /dev/null +++ b/scripts/leios-demo/demo_analysis.ipynb @@ -0,0 +1,110 @@ +{ + "cells": [ + { + "cell_type": "code", + "execution_count": null, + "id": "34d6fcb0-7a19-4bcd-940f-4553a53b2334", + "metadata": {}, + "outputs": [], + "source": [ + "import json\n", + "import pandas as pd\n", + "import altair as alt\n", + "from itables import init_notebook_mode\n", + "\n", + "init_notebook_mode(all_interactive=True)\n", + "\n", + "def df_from_cardano_node_logs(fp):\n", + " lines = open(fp, \"r\").readlines()\n", + " at_lines = [ json.loads(line) for line in lines if line.startswith('{\"at') ]\n", + " return pd.DataFrame.from_records(at_lines)\n", + "\n", + "cardano_node_0_df = df_from_cardano_node_logs(\"data/cardano-node-0.log\")\n", + "cardano_node_1_df = df_from_cardano_node_logs(\"data/cardano-node-1.log\")\n", + "\n", + "all_logs = pd.concat([cardano_node_0_df.assign(source=\"cardano-node-0\"), cardano_node_1_df.assign(source=\"cardano-node-1\")])\n", + "\n", + "all_logs" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "9b14673f-2800-47fa-97e6-44723bacebd5", + "metadata": {}, + "outputs": [], + "source": [ + "# SELECT * FROM all_logs WHERE sev = 'Critical'\n", + "all_logs[all_logs.sev == \"Critical\"]" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "6fa79265-32db-4834-b54c-e7362fa5ece1", + "metadata": {}, + "outputs": [], + "source": [ + "# SELECT DISTINCT_COUNT(ns), ARG_MAX(ns), ARG_MIN(ns), ARG_MAX(sev), ARG_MIN(sev) FROM all_logs GROUP BY source \n", + "all_logs.groupby('source').agg({\n", + " 'ns': ['nunique', 'max', 'min'],\n", + " 'sev': ['max', 'min']\n", + "})" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "331c6927-efe0-461c-b504-bce026f94b14", + "metadata": {}, + "outputs": [], + "source": [ + "all_logs.groupby('ns').count()" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "147ede1a-0363-434d-bea8-e1f51219a56f", + "metadata": {}, + "outputs": [], + "source": [ + "latency_logs_df = all_logs[all_logs.ns.isin([\"BlockFetch.Client.CompletedBlockFetch\", \"ChainSync.Client.DownloadedHeader\"])]\n", + "latency_logs_df.loc[:, 'block'] = latency_logs_df.apply(lambda r: r.data['block'], axis=1)" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "8892142d-3487-4b9e-a0cc-a1cebdc77df6", + "metadata": {}, + "outputs": [], + "source": [ + "latency_logs_df.groupby(['block', 'source', 'ns']).agg({\n", + " 'at': ['count', 'min', 'max']\n", + "})" + ] + } + ], + "metadata": { + "kernelspec": { + "display_name": "Python 3 (ipykernel)", + "language": "python", + "name": "python3" + }, + "language_info": { + "codemirror_mode": { + "name": "ipython", + "version": 3 + }, + "file_extension": ".py", + "mimetype": "text/x-python", + "name": "python", + "nbconvert_exporter": "python", + "pygments_lexer": "ipython3", + "version": "3.13.8" + } + }, + "nbformat": 4, + "nbformat_minor": 5 +} diff --git a/scripts/leios-demo/requirements.txt b/scripts/leios-demo/requirements.txt index 56552f0d9f..688e3e8105 100644 --- a/scripts/leios-demo/requirements.txt +++ b/scripts/leios-demo/requirements.txt @@ -12,3 +12,5 @@ python-dateutil==2.9.0.post0 pytz==2025.2 six==1.17.0 tzdata==2025.2 +altair==5.2.0 +itables==2.5.2 From 0bd849832842fea0d29872d7c0728476cef6004e Mon Sep 17 00:00:00 2001 From: dnadales Date: Tue, 21 Oct 2025 16:30:02 -0300 Subject: [PATCH 036/119] Thread the onset of the reference slot through the immdb-server code --- .../app/immdb-server.hs | 27 ++++++++++++++++--- .../ouroboros-consensus-cardano.cabal | 3 +++ .../Cardano/Tools/ImmDBServer/Diffusion.hs | 8 +++--- .../Tools/ImmDBServer/MiniProtocols.hs | 13 +++++++-- 4 files changed, 43 insertions(+), 8 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index 5e118362ef..7bc73678b2 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -12,23 +12,34 @@ import Main.Utf8 (withStdTerminalHandles) import qualified Network.Socket as Socket import Options.Applicative import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) +import Cardano.Slotting.Slot (SlotNo (..)) +import qualified Data.Time.Clock.POSIX as POSIX main :: IO () main = withStdTerminalHandles $ do cryptoInit - Opts {immDBDir, port, configFile} <- execParser optsParser + Opts {immDBDir, port, configFile, refSlotNr, refTimeForRefSlot} + <- execParser optsParser let sockAddr = Socket.SockAddrInet port hostAddr where -- could also be passed in hostAddr = Socket.tupleToHostAddress (127, 0, 0, 1) args = Cardano.CardanoBlockArgs configFile Nothing ProtocolInfo{pInfoConfig} <- mkProtocolInfo args - absurd <$> ImmDBServer.run immDBDir sockAddr pInfoConfig + let onsetRefSlot = ImmDBServer.OnsetRefSlot refSlotNr refTimeForRefSlot + absurd <$> ImmDBServer.run immDBDir sockAddr pInfoConfig onsetRefSlot data Opts = Opts { immDBDir :: FilePath , port :: Socket.PortNumber , configFile :: FilePath + , refSlotNr :: SlotNo + -- ^ Reference slot number. This, in combination with the reference + -- time will be used to convert between slot number and wallclock time. + -- N.B.: for now we assume the slot duration to be 1 second. + , refTimeForRefSlot :: POSIX.POSIXTime + -- ^ Reference slot onset. Wallclock time that corresponds to the + -- reference slot. } optsParser :: ParserInfo Opts @@ -54,4 +65,14 @@ optsParser = , help "Path to config file, in the same format as for the node or db-analyser" , metavar "PATH" ] - pure Opts {immDBDir, port, configFile} + refSlotNr <- fmap SlotNo $ option auto $ mconcat + [ long "initial-slot" + , help "Reference slot number (SlotNo). This, together with the initial-time will be used for time translations." + , metavar "SLOT_NO" + ] + refTimeForRefSlot <- option auto $ mconcat + [ long "initial-time" + , help "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)" + , metavar "POSIX_SECONDS" + ] + pure Opts {immDBDir, port, configFile, refSlotNr, refTimeForRefSlot} diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index 86fa8bfaf0..617d036dd7 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -586,6 +586,7 @@ library unstable-cardano-tools sop-core, sop-extras, strict-sop-core, + time, text, text-builder >=1, transformers, @@ -673,11 +674,13 @@ executable immdb-server build-depends: base, cardano-crypto-class, + cardano-slotting, network, optparse-applicative, ouroboros-consensus, ouroboros-consensus-cardano:unstable-cardano-tools, with-utf8, + time executable snapshot-converter import: common-exe diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index ed6142daa7..b032a92a6e 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -3,9 +3,9 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} -module Cardano.Tools.ImmDBServer.Diffusion (run) where +module Cardano.Tools.ImmDBServer.Diffusion (run, OnsetRefSlot (..)) where -import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) +import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, OnsetRefSlot (..)) import Control.ResourceRegistry import Control.Tracer import qualified Data.ByteString.Lazy as BL @@ -82,8 +82,9 @@ run :: => FilePath -> SockAddr -> TopLevelConfig blk + -> OnsetRefSlot -> IO Void -run immDBDir sockAddr cfg = withRegistry \registry -> +run immDBDir sockAddr cfg onsetRefSlot = withRegistry \registry -> ImmutableDB.withDB (ImmutableDB.openDB (immDBArgs registry) runWithTempRegistry) \immDB -> serve sockAddr $ immDBServer @@ -92,6 +93,7 @@ run immDBDir sockAddr cfg = withRegistry \registry -> decodeRemoteAddress immDB networkMagic + onsetRefSlot where immDBArgs registry = ImmutableDB.defaultArgs { immCheckIntegrity = nodeCheckIntegrity storageCfg diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 288be36eb0..da7194e3ae 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -12,7 +12,7 @@ {-# LANGUAGE TypeApplications #-} -- | Implement ChainSync and BlockFetch servers on top of just the immutable DB. -module Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) where +module Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, OnsetRefSlot(..)) where import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR @@ -60,6 +60,14 @@ import Ouroboros.Network.Protocol.ChainSync.Server import Ouroboros.Network.Protocol.Handshake.Version (Version (..)) import Ouroboros.Network.Protocol.KeepAlive.Server (keepAliveServerPeer) +import qualified Data.Time.Clock.POSIX as POSIX + +-- | Onset of the reference slot. Used for conversions between +-- wallclock time and slot number. +data OnsetRefSlot = + OnsetRefSlot { slot :: SlotNo, + onset :: POSIX.POSIXTime + } immDBServer :: forall m blk addr. @@ -74,9 +82,10 @@ immDBServer :: -> (NodeToNodeVersion -> forall s . CBOR.Decoder s addr) -> ImmutableDB m blk -> NetworkMagic + -> OnsetRefSlot -> Versions NodeToNodeVersion NodeToNodeVersionData (OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode addr BL.ByteString m Void ()) -immDBServer codecCfg encAddr decAddr immDB networkMagic = do +immDBServer codecCfg encAddr decAddr immDB networkMagic onsetRefSlot = do forAllVersions application where forAllVersions :: From 089702bf98b7b010ca236a50cfbcf57d969aa116 Mon Sep 17 00:00:00 2001 From: dnadales Date: Tue, 21 Oct 2025 18:08:14 -0300 Subject: [PATCH 037/119] Pass a function that abstracts away slot delay calculation --- .../app/immdb-server.hs | 8 +++++-- .../ouroboros-consensus-cardano.cabal | 1 - .../Cardano/Tools/ImmDBServer/Diffusion.hs | 10 ++++---- .../Tools/ImmDBServer/MiniProtocols.hs | 24 ++++++++----------- 4 files changed, 21 insertions(+), 22 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index 7bc73678b2..2b8e0c4ba5 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -26,8 +26,12 @@ main = withStdTerminalHandles $ do hostAddr = Socket.tupleToHostAddress (127, 0, 0, 1) args = Cardano.CardanoBlockArgs configFile Nothing ProtocolInfo{pInfoConfig} <- mkProtocolInfo args - let onsetRefSlot = ImmDBServer.OnsetRefSlot refSlotNr refTimeForRefSlot - absurd <$> ImmDBServer.run immDBDir sockAddr pInfoConfig onsetRefSlot + absurd <$> ImmDBServer.run immDBDir + sockAddr + pInfoConfig + (mkGetSlotDelay refSlotNr refTimeForRefSlot) + where + mkGetSlotDelay = undefined data Opts = Opts { immDBDir :: FilePath diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index 617d036dd7..d6c7d27140 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -586,7 +586,6 @@ library unstable-cardano-tools sop-core, sop-extras, strict-sop-core, - time, text, text-builder >=1, transformers, diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index b032a92a6e..a1171e912a 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -3,9 +3,9 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} -module Cardano.Tools.ImmDBServer.Diffusion (run, OnsetRefSlot (..)) where +module Cardano.Tools.ImmDBServer.Diffusion (run) where -import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, OnsetRefSlot (..)) +import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) import Control.ResourceRegistry import Control.Tracer import qualified Data.ByteString.Lazy as BL @@ -82,9 +82,9 @@ run :: => FilePath -> SockAddr -> TopLevelConfig blk - -> OnsetRefSlot + -> (WithOrigin SlotNo -> IO DiffTime) -> IO Void -run immDBDir sockAddr cfg onsetRefSlot = withRegistry \registry -> +run immDBDir sockAddr cfg getSlotDelay = withRegistry \registry -> ImmutableDB.withDB (ImmutableDB.openDB (immDBArgs registry) runWithTempRegistry) \immDB -> serve sockAddr $ immDBServer @@ -93,7 +93,7 @@ run immDBDir sockAddr cfg onsetRefSlot = withRegistry \registry -> decodeRemoteAddress immDB networkMagic - onsetRefSlot + getSlotDelay where immDBArgs registry = ImmutableDB.defaultArgs { immCheckIntegrity = nodeCheckIntegrity storageCfg diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index da7194e3ae..7d71840bdb 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -12,7 +12,7 @@ {-# LANGUAGE TypeApplications #-} -- | Implement ChainSync and BlockFetch servers on top of just the immutable DB. -module Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, OnsetRefSlot(..)) where +module Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) where import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR @@ -60,14 +60,6 @@ import Ouroboros.Network.Protocol.ChainSync.Server import Ouroboros.Network.Protocol.Handshake.Version (Version (..)) import Ouroboros.Network.Protocol.KeepAlive.Server (keepAliveServerPeer) -import qualified Data.Time.Clock.POSIX as POSIX - --- | Onset of the reference slot. Used for conversions between --- wallclock time and slot number. -data OnsetRefSlot = - OnsetRefSlot { slot :: SlotNo, - onset :: POSIX.POSIXTime - } immDBServer :: forall m blk addr. @@ -82,10 +74,10 @@ immDBServer :: -> (NodeToNodeVersion -> forall s . CBOR.Decoder s addr) -> ImmutableDB m blk -> NetworkMagic - -> OnsetRefSlot + -> (WithOrigin SlotNo -> m DiffTime) -> Versions NodeToNodeVersion NodeToNodeVersionData (OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode addr BL.ByteString m Void ()) -immDBServer codecCfg encAddr decAddr immDB networkMagic onsetRefSlot = do +immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay = do forAllVersions application where forAllVersions :: @@ -151,7 +143,7 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic onsetRefSlot = do withRegistry $ runPeer nullTracer cChainSyncCodecSerialised channel . chainSyncServerPeer - . chainSyncServer immDB ChainDB.getSerialisedHeaderWithPoint + . chainSyncServer immDB ChainDB.getSerialisedHeaderWithPoint getSlotDelay blockFetchProt = MiniProtocolCb $ \_ctx channel -> withRegistry @@ -182,9 +174,10 @@ chainSyncServer :: forall m blk a. (IOLike m, HasHeader blk) => ImmutableDB m blk -> BlockComponent blk (ChainDB.WithPoint blk a) + -> (WithOrigin SlotNo -> m DiffTime) -> ResourceRegistry m -> ChainSyncServer a (Point blk) (Tip blk) m () -chainSyncServer immDB blockComponent registry = ChainSyncServer $ do +chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ do follower <- newImmutableDBFollower runChainSyncServer $ chainSyncServerForFollower nullTracer getImmutableTip follower @@ -209,7 +202,10 @@ chainSyncServer immDB blockComponent registry = ChainSyncServer $ do ImmutableDB.IteratorExhausted -> do ImmutableDB.iteratorClose iterator throwIO ReachedImmutableTip - ImmutableDB.IteratorResult a -> + ImmutableDB.IteratorResult a -> do + -- Wait until the slot of the current block has been reached + slotDelay <- getSlotDelay $ pointSlot $ ChainDB.point a + threadDelay slotDelay pure $ AddBlock a followerClose = ImmutableDB.iteratorClose =<< readTVarIO varIterator From 0945ffd32ebcb99f3539ec431f72f1b91ab871e0 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Wed, 22 Oct 2025 12:37:02 +0200 Subject: [PATCH 038/119] Freeze the Python environment from Nix into requirements.txt $ pip freeze > requirements.txt --- scripts/leios-demo/build.nix | 7 +- scripts/leios-demo/demo_analysis.ipynb | 128 ++++++++++++++++++++---- scripts/leios-demo/requirements.txt | 132 ++++++++++++++++++++++--- 3 files changed, 235 insertions(+), 32 deletions(-) diff --git a/scripts/leios-demo/build.nix b/scripts/leios-demo/build.nix index 30647deab9..1e587547bd 100644 --- a/scripts/leios-demo/build.nix +++ b/scripts/leios-demo/build.nix @@ -13,9 +13,14 @@ pip virtualenv python-lsp-server - jupyterlab black itables + ipywidgets + jupyterlab-widgets + widgetsnbextension + jupyterlab + jupyter + venvShellHook nixpkgs-fmt nil diff --git a/scripts/leios-demo/demo_analysis.ipynb b/scripts/leios-demo/demo_analysis.ipynb index 40ebd6126f..c6f0fee61a 100644 --- a/scripts/leios-demo/demo_analysis.ipynb +++ b/scripts/leios-demo/demo_analysis.ipynb @@ -1,83 +1,171 @@ { "cells": [ + { + "cell_type": "markdown", + "id": "c4106e57-a8de-4200-9ad1-2eab21bedbbd", + "metadata": {}, + "source": [ + "## Imports" + ] + }, { "cell_type": "code", "execution_count": null, "id": "34d6fcb0-7a19-4bcd-940f-4553a53b2334", - "metadata": {}, + "metadata": { + "jupyter": { + "source_hidden": true + } + }, "outputs": [], "source": [ "import json\n", "import pandas as pd\n", "import altair as alt\n", "from itables import init_notebook_mode\n", + "import ipywidgets as widgets\n", "\n", - "init_notebook_mode(all_interactive=True)\n", - "\n", + "init_notebook_mode(all_interactive=True)" + ] + }, + { + "cell_type": "markdown", + "id": "b30e49a3-01f2-4941-9521-9fcfb7ae1985", + "metadata": {}, + "source": [ + "## Load data" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "fb9e23cd-9257-40a4-bd56-2e76797294a5", + "metadata": { + "jupyter": { + "source_hidden": true + } + }, + "outputs": [], + "source": [ + "# cardano_node_0_df, cardano_node_0_df and all_df\n", "def df_from_cardano_node_logs(fp):\n", " lines = open(fp, \"r\").readlines()\n", " at_lines = [ json.loads(line) for line in lines if line.startswith('{\"at') ]\n", " return pd.DataFrame.from_records(at_lines)\n", "\n", + "def events_chart(df, eventPrefix):\n", + " return alt.Chart(df[df.ns.str.startswith(eventPrefix)].reset_index()).mark_point().encode(\n", + " x='at:T',\n", + " y='source',\n", + " color='ns',\n", + " tooltip='ns'\n", + " ).interactive()\n", + "\n", "cardano_node_0_df = df_from_cardano_node_logs(\"data/cardano-node-0.log\")\n", "cardano_node_1_df = df_from_cardano_node_logs(\"data/cardano-node-1.log\")\n", "\n", - "all_logs = pd.concat([cardano_node_0_df.assign(source=\"cardano-node-0\"), cardano_node_1_df.assign(source=\"cardano-node-1\")])\n", + "all_df = pd.concat([cardano_node_0_df.assign(source=\"cardano-node-0\"), cardano_node_1_df.assign(source=\"cardano-node-1\")])\n", "\n", - "all_logs" + "all_df" + ] + }, + { + "cell_type": "markdown", + "id": "8c524cdc-5d04-4e92-a18d-632441c61fb0", + "metadata": {}, + "source": [ + "## Quick refresher" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "b3a4c630-bec8-433d-9bbd-1c7510ab7606", + "metadata": { + "editable": true, + "jupyter": { + "source_hidden": true + }, + "slideshow": { + "slide_type": "" + }, + "tags": [] + }, + "outputs": [], + "source": [ + "# ChainSync events\n", + "\n", + "events_chart(all_df, 'ChainSync')" ] }, { "cell_type": "code", "execution_count": null, "id": "9b14673f-2800-47fa-97e6-44723bacebd5", - "metadata": {}, + "metadata": { + "jupyter": { + "source_hidden": true + } + }, "outputs": [], "source": [ - "# SELECT * FROM all_logs WHERE sev = 'Critical'\n", - "all_logs[all_logs.sev == \"Critical\"]" + "# SELECT * FROM all_df WHERE sev = 'Error'\n", + "display(events_chart(all_df[all_df.sev == \"Error\"], \"\"))\n", + "all_df[all_df.sev == \"Error\"]" ] }, { "cell_type": "code", "execution_count": null, "id": "6fa79265-32db-4834-b54c-e7362fa5ece1", - "metadata": {}, + "metadata": { + "jupyter": { + "source_hidden": true + } + }, "outputs": [], "source": [ - "# SELECT DISTINCT_COUNT(ns), ARG_MAX(ns), ARG_MIN(ns), ARG_MAX(sev), ARG_MIN(sev) FROM all_logs GROUP BY source \n", - "all_logs.groupby('source').agg({\n", + "# SELECT DISTINCT_COUNT(ns), ARG_MAX(ns), ARG_MIN(ns), ARG_MAX(sev), ARG_MIN(sev) FROM all_df GROUP BY source \n", + "all_df.groupby('source').agg({\n", " 'ns': ['nunique', 'max', 'min'],\n", " 'sev': ['max', 'min']\n", "})" ] }, { - "cell_type": "code", - "execution_count": null, - "id": "331c6927-efe0-461c-b504-bce026f94b14", + "cell_type": "markdown", + "id": "76191267-de35-47c0-ba9d-90276a552c13", "metadata": {}, - "outputs": [], "source": [ - "all_logs.groupby('ns').count()" + "## Latency" ] }, { "cell_type": "code", "execution_count": null, "id": "147ede1a-0363-434d-bea8-e1f51219a56f", - "metadata": {}, + "metadata": { + "jupyter": { + "source_hidden": true + } + }, "outputs": [], "source": [ - "latency_logs_df = all_logs[all_logs.ns.isin([\"BlockFetch.Client.CompletedBlockFetch\", \"ChainSync.Client.DownloadedHeader\"])]\n", - "latency_logs_df.loc[:, 'block'] = latency_logs_df.apply(lambda r: r.data['block'], axis=1)" + "latency_logs_df = all_df[all_df.ns.isin([\"BlockFetch.Client.CompletedBlockFetch\", \"ChainSync.Client.DownloadedHeader\"])]\n", + "latency_logs_df = latency_logs_df.assign(\n", + " block=latency_logs_df.data.apply(lambda r: r['block']),\n", + ")" ] }, { "cell_type": "code", "execution_count": null, "id": "8892142d-3487-4b9e-a0cc-a1cebdc77df6", - "metadata": {}, + "metadata": { + "jupyter": { + "source_hidden": true + } + }, "outputs": [], "source": [ "latency_logs_df.groupby(['block', 'source', 'ns']).agg({\n", diff --git a/scripts/leios-demo/requirements.txt b/scripts/leios-demo/requirements.txt index 688e3e8105..9a2152851d 100644 --- a/scripts/leios-demo/requirements.txt +++ b/scripts/leios-demo/requirements.txt @@ -1,16 +1,126 @@ -contourpy==1.3.3 -cycler==0.12.1 -fonttools==4.60.1 -kiwisolver==1.4.9 -matplotlib==3.10.7 -numpy==2.3.4 +altair==5.5.0 +anyio==4.11.0 +argon2-cffi==25.1.0 +argon2-cffi-bindings==25.1.0 +arrow==1.3.0 +asttokens==3.0.0 +async-lru==2.0.5 +attrs==25.3.0 +babel==2.17.0 +beautifulsoup4==4.13.4 +black==25.1.0 +bleach==6.2.0 +certifi==2025.7.14 +cffi==2.0.0 +charset-normalizer==3.4.3 +click==8.2.1 +comm==0.2.3 +decorator==5.2.1 +defusedxml==0.8.0rc2 +distlib==0.4.0 +docstring-to-markdown==0.17 +executing==2.2.0 +fastjsonschema==2.21.1 +filelock==3.18.0 +flit_core==3.12.0 +fqdn==1.5.1 +h11==0.16.0 +html5lib==1.1 +httpcore==1.0.9 +httpx==0.28.1 +idna==3.10 +importlib_metadata==8.7.0 +ipykernel==6.30.1 +ipython==9.5.0 +ipython_pygments_lexers==1.1.1 +ipywidgets==8.1.7 +isoduration==20.11.0 +itables==2.5.2 +jedi==0.19.2 +Jinja2==3.1.6 +json5==0.12.0 +jsonpath-ng==1.7.0 +jsonpointer==3.0.0 +jsonschema==4.25.0 +jsonschema-specifications==2025.4.1 +jupyter==1.1.1 +jupyter-console==6.6.3 +jupyter-events==0.12.0 +jupyter-lsp==2.2.6 +jupyter_client==8.6.3 +jupyter_core==5.8.1 +jupyter_server==2.16.0 +jupyter_server_terminals==0.5.3 +jupyterlab==4.4.5 +jupyterlab_pygments==0.3.0 +jupyterlab_server==2.27.3 +jupyterlab_widgets==3.0.15 +lark==1.2.2 +MarkupSafe==3.0.3 +matplotlib-inline==0.1.7 +mistune==3.1.4 +mypy_extensions==1.1.0 +narwhals==2.6.0 +nbclient==0.10.2 +nbconvert==7.16.6 +nbformat==5.10.4 +nest_asyncio==1.6.0 +notebook==7.4.4 +notebook_shim==0.2.4 +numpy==2.3.3 +overrides==7.7.0 packaging==25.0 -pandas==2.3.3 -pillow==12.0.0 -pyparsing==3.2.5 +pandas==2.3.1 +pandocfilters==1.5.1 +parso==0.8.4 +pathspec==0.12.1 +pexpect==4.9.0 +platformdirs==4.3.8 +pluggy==1.6.0 +ply==3.11 +prometheus_client==0.22.1 +prompt_toolkit==3.0.52 +psutil==7.1.0 +ptyprocess==0.7.0 +pure_eval==0.2.3 +pycparser==2.23 +Pygments==2.19.2 python-dateutil==2.9.0.post0 +python-json-logger==3.3.0 +python-lsp-jsonrpc==1.1.2 +python-lsp-server==1.13.1 pytz==2025.2 +PyYAML==6.0.3 +pyzmq==27.0.1 +referencing==0.36.2 +regex==2025.7.34 +requests==2.32.5 +rfc3339_validator==0.1.4 +rfc3986_validator==0.1.1 +rfc3987-syntax==1.1.0 +rpds-py==0.25.0 +Send2Trash==1.8.3 +setuptools==80.9.0.post0 six==1.17.0 +sniffio==1.3.1 +soupsieve==2.7 +stack_data==0.6.3 +terminado==0.18.1 +tinycss2==1.4.0 +toml==0.10.2 +toolz==1.0.0 +tornado==6.5.1 +traitlets==5.14.3 +types-python-dateutil==2.9.0.20250708 +typing_extensions==4.15.0 tzdata==2025.2 -altair==5.2.0 -itables==2.5.2 +ujson==5.10.0 +uri-template==1.3.0 +urllib3==2.5.0 +virtualenv==20.33.1 +wcwidth==0.2.13 +webcolors==24.11.1 +webencodings==0.5.1 +websocket-client==1.8.0 +widgetsnbextension==4.0.14 +zipp==3.23.0 From 59587e8f5868c19c353bc5db62d0873ea8632f89 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 22 Oct 2025 11:39:12 -0700 Subject: [PATCH 039/119] leiosdemo202510: redo the fetch iteration logic and MsgLeiosBlockTxs now also updates that same state --- ouroboros-consensus/app/leiosdemo202510.hs | 780 ++++++++++++++++-- ouroboros-consensus/ouroboros-consensus.cabal | 3 + 2 files changed, 692 insertions(+), 91 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 5a4c488646..c40c6ab655 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -2,11 +2,13 @@ {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TypeApplications #-} -module Main (main) where +module Main (module Main) where import Cardano.Binary (serialize') import qualified Cardano.Crypto.Hash as Hash @@ -21,11 +23,20 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Char8 as BS8 import qualified Data.ByteString.Lazy as BSL +import Data.DList (DList) +import qualified Data.DList as DList import Data.Foldable (forM_) +import Data.Functor.Contravariant ((>$<)) import qualified Data.IntMap as IntMap -import qualified Data.IntSet as IntSet +import Data.IntMap (IntMap) import Data.List (intercalate, isSuffixOf, unfoldr) +import Data.Map (Map) +import qualified Data.Map as Map +import Data.Set (Set) +import qualified Data.Set as Set import Data.String (fromString) +import qualified Data.Text as T +import qualified Data.Text.Encoding as T (decodeUtf8', encodeUtf8) import qualified Data.Vector as V import Data.Word (Word8, Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB @@ -39,67 +50,91 @@ import qualified System.Random.Stateful as R import Text.Read (readMaybe) main :: IO () -main = getArgs >>= \case - ["generate", dbPath, manifestPath] +main = flip asTypeOf main2 $ do + main2 + +main2 :: IO () +main2 = getArgs >>= \case + ["generate", dbPath, lfstPath, manifestPath] | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath , ".json" `isSuffixOf` manifestPath -> do doesFileExist dbPath >>= \case True -> die "database path must not exist" False -> pure () + doesFileExist lfstPath >>= \case + True -> die "LeiosFetchState path must not exist" + False -> pure () manifest <- fmap JSON.eitherDecode (BSL.readFile manifestPath) >>= \case Left err -> die err Right x -> pure x db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen generateDb prng0 db manifest + JSON.encodeFile lfstPath emptyLeiosFetchState ["MsgLeiosBlockRequest", dbPath, ebIdStr] | ".db" `isSuffixOf` dbPath , Just ebId <- readMaybe ebIdStr -> do db <- withDieMsg $ DB.open (fromString dbPath) msgLeiosBlockRequest db ebId - ["MsgLeiosBlock", dbPath, ebIdStr, ebSlotStr, ebPath] + ["MsgLeiosBlock", dbPath, ebSlotStr, ebPath] | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebPath - , Just ebId <- readMaybe ebIdStr , Just ebSlot <- readMaybe ebSlotStr -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlock db ebId ebSlot ebPath - "MsgLeiosBlockTxsRequest" : dbPath : ebIdStr : bitmapChunkStrs + msgLeiosBlock db ebSlot ebPath + "MsgLeiosBlockTxsRequest" : dbPath : slotStr : hashStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath - , Just ebId <- readMaybe ebIdStr + , Just slot <- readMaybe slotStr + , Right hash <- BS16.decode $ BS8.pack hashStr , Just bitmaps <- parseBitmaps bitmapChunkStrs -> do db <- withDieMsg $ DB.open (fromString dbPath) + dynEnv <- loadLeiosFetchDynEnvHelper False db + let ebId = fst $ ebIdFromPoint slot hash dynEnv msgLeiosBlockTxsRequest db ebId bitmaps - "MsgLeiosBlockTxs" : dbPath : ebIdStr : ebTxsPath : bitmapChunkStrs + ["MsgLeiosBlockTxs", dbPath, lfstPath, peerIdStr, ebTxsPath] | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebTxsPath - , Just ebId <- readMaybe ebIdStr - , Just bitmaps <- parseBitmaps bitmapChunkStrs + , not (null peerIdStr) -> do db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlockTxs db ebId ebTxsPath bitmaps - "fetch-decision" : dbPath : ebIdStrs - | ".db" `isSuffixOf` dbPath - , Just ebIds <- sequence $ map readMaybe ebIdStrs + dynEnv <- loadLeiosFetchDynEnvHelper False db + acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + acc' <- msgLeiosBlockTxs db dynEnv acc (MkPeerId peerIdStr) ebTxsPath + JSON.encodeFile lfstPath acc' + "MsgLeiosBlockTxsOffer" : lfstPath : peerIdStr : ebIdStrs + | ".lfst" `isSuffixOf` lfstPath + , not (null peerIdStr) + , Just ebIds <- map MkEbId <$> traverse readMaybe ebIdStrs , not (null ebIds) + -> do + acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + acc' <- msgLeiosBlockTxsOffer acc (MkPeerId peerIdStr) ebIds + JSON.encodeFile lfstPath acc' + ["fetch-logic-iteration", dbPath, lfstPath] + | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath -> do db <- withDieMsg $ DB.open (fromString dbPath) - fetchDecision db (IntSet.fromList ebIds) + acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + acc' <- fetchDecision2 db acc + JSON.encodeFile lfstPath acc' ["hash-txs", ebTxsPath] | ".bin" `isSuffixOf` ebTxsPath -> do hashTxs ebTxsPath - _ -> die "Either $0 generate myDatabase.db myManifest.json\n\ - \ OR $0 MsgLeiosBlockRequest myDatabase.db ebId\n\ - \ OR $0 MsgLeiosBlock myDatabase.db ebId myEb.bin\n\ - \ OR $0 MsgLeiosBlockTxsRequest myDatabase.db ebId index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ - \ OR $0 MsgLeiosBlockTxs myDatabase.db ebId myEbTxs.bin index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ - \ OR $0 fetch-decision myDatabase.db ebId ebId ebId ...\n\ + _ -> die "Either $0 generate my.db myManifest.json\n\ + \ OR $0 MsgLeiosBlockRequest my.db ebId\n\ + \ OR $0 MsgLeiosBlock my.db ebId myEb.bin\n\ + \ OR $0 MsgLeiosBlockTxsRequest my.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlockTxs my.db my.lfst peerId myEbTxs.bin\n\ + \ OR $0 fetch-logic-iteration my.db my.lfst\n\ \ OR $0 hash-txs myEbTxs.bin\n\ + \ OR $0 MsgLeiosBlockTxsOffer my.lfst peerId ebId ebId ebId ...\n\ \" parseBitmaps :: [String] -> Maybe [(Word16, Word64)] @@ -115,15 +150,21 @@ parseBitmaps = -> go ((idx, bitmap) : acc) bitmapChunkStrs _ -> Nothing +prettyBitmap :: (Word16, Word64) -> String +prettyBitmap (idx, bitmap) = + show idx ++ ":0x" ++ Numeric.showHex bitmap "" + data EbRecipe = EbRecipe { - slotNo :: Word64 + ebRecipeSlotNo :: Word64 , - txByteSizes :: V.Vector Word16 + ebRecipeTxBytesSizes :: V.Vector Word16 } deriving (Generic, Show) --- | defaults to @GHC.Generics@ -instance JSON.FromJSON EbRecipe where {} +instance JSON.FromJSON EbRecipe where + parseJSON = JSON.withObject "EbRecipe" $ \v -> EbRecipe + <$> v JSON..: (fromString "slotNo") + <*> v JSON..: (fromString "txBytesSizes") ----- @@ -137,34 +178,36 @@ generateDb prng0 db ebRecipes = do stmt_write_ebId <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) - forM_ ([(0 :: Word16) ..] `zip` ebRecipes) $ \(ebId, ebRecipe) -> do + _dynEnv' <- (\f -> foldM f emptyLeiosFetchDynEnv ebRecipes) $ \dynEnv ebRecipe -> do -- generate txs, so we have their hashes - txs <- V.forM (txByteSizes ebRecipe) $ \txByteSize -> do + txs <- V.forM (ebRecipeTxBytesSizes ebRecipe) $ \txBytesSize -> do -- generate a random bytestring whose CBOR encoding has the expected length -- -- In the actual implementation, the values themselves will be -- valid CBOR. It's useful to maintain that invariant even for the -- otherwise-opaque random data within this prototype/demo. - when (txByteSize < 55) $ die "Tx cannot be smaller than 55 bytes" + when (txBytesSize < 55) $ die "Tx cannot be smaller than 55 bytes" let overhead -- one for the initial byte, plus 1 2 4 or 8 for the length argument - | txByteSize < fromIntegral (maxBound :: Word8) = 2 - | txByteSize < (maxBound :: Word16) = 3 - | txByteSize < fromIntegral (maxBound :: Word32) = 5 + | txBytesSize < fromIntegral (maxBound :: Word8) = 2 + | txBytesSize < (maxBound :: Word16) = 3 + | txBytesSize < fromIntegral (maxBound :: Word32) = 5 | otherwise = 9 txBytes <- id $ fmap (serialize' . CBOR.encodeBytes) - $ R.uniformByteStringM (fromIntegral txByteSize - overhead) gref + $ R.uniformByteStringM (fromIntegral txBytesSize - overhead) gref pure (txBytes, Hash.hashWith id txBytes :: Hash.Hash HASH ByteString) - let ebSlot = slotNo ebRecipe + let ebSlot = ebRecipeSlotNo ebRecipe let ebHash :: Hash.Hash HASH ByteString ebHash = Hash.castHash $ Hash.hashWithSerialiser (encodeEB (fromIntegral . BS.length) Hash.hashToBytes) txs + + let (ebId, dynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv withDieMsg $ DB.exec db (fromString "BEGIN") - withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegral ebId) - withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegralEbId ebId) + withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegralEbId ebId) -- INSERT INTO ebPoints withDie $ DB.bindInt64 stmt_write_ebId 1 (fromIntegral ebSlot) withDie $ DB.bindBlob stmt_write_ebId 2 (Hash.hashToBytes ebHash) @@ -181,6 +224,7 @@ generateDb prng0 db ebRecipes = do withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") + pure dynEnv' -- finalize db withDieMsg $ DB.exec db (fromString sql_index_schema) @@ -213,7 +257,7 @@ sql_schema = \ ,\n\ \ txHashBytes BLOB NOT NULL -- raw bytes\n\ \ ,\n\ - \ txByteSize INTEGER NOT NULL\n\ + \ txBytesSize INTEGER NOT NULL\n\ \ ,\n\ \ txBytes BLOB -- valid CBOR\n\ \ ,\n\ @@ -224,17 +268,17 @@ sql_schema = sql_index_schema :: String sql_index_schema = "CREATE INDEX ebPointsExpiry\n\ - \ ON ebPoints (ebSlot, ebId); -- Helps with the eviction policy of the EbStore.\n\ + \ ON ebPoints (ebSlot ASC, ebId ASC); -- Helps with the eviction policy of the EbStore.\n\ \\n\ \CREATE INDEX txCacheExpiry\n\ - \ ON txCache (expiryUnixEpoch, txHashBytes); -- Helps with the eviction policy of the TxCache.\n\ + \ ON txCache (expiryUnixEpoch ASC, txHashBytes); -- Helps with the eviction policy of the TxCache.\n\ \\n\ \CREATE INDEX missingEbTxs\n\ - \ ON ebTxs (ebId, txOffset)\n\ + \ ON ebTxs (ebId DESC, txOffset ASC)\n\ \ WHERE txBytes IS NULL; -- Helps with fetch logic decisions.\n\ \\n\ \CREATE INDEX acquiredEbTxs\n\ - \ ON ebTxs (ebId, txOffset)\n\ + \ ON ebTxs (ebId DESC, txOffset ASC)\n\ \ WHERE txBytes IS NOT NULL; -- Helps with fetch logic decisions.\n\ \" @@ -245,7 +289,7 @@ sql_insert_ebId = sql_insert_ebClosure :: String sql_insert_ebClosure = - "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ + "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txBytesSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ \" ----- @@ -335,8 +379,8 @@ msgLeiosBlockRequest db ebId = do DB.Row -> do -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? txHashBytes <- DB.columnBlob stmt 0 - txByteSize <- DB.columnInt64 stmt 1 - loop $ pushX acc (txByteSize, txHashBytes) + txBytesSize <- DB.columnInt64 stmt 1 + loop $ pushX acc (txBytesSize, txHashBytes) acc <- loop emptyX -- combine the EB items BS.putStr @@ -349,12 +393,12 @@ msgLeiosBlockRequest db ebId = do -- logic naturally reverses it sql_lookup_ebBodies_DESC :: String sql_lookup_ebBodies_DESC = - "SELECT txHashBytes, txByteSize FROM ebTxs\n\ + "SELECT txHashBytes, txBytesSize FROM ebTxs\n\ \WHERE ebId = ?\n\ \ORDER BY txOffset DESC\n\ \" -msgLeiosBlockTxsRequest :: DB.Database -> Int -> [(Word16, Word64)] -> IO () +msgLeiosBlockTxsRequest :: DB.Database -> EbId -> [(Word16, Word64)] -> IO () msgLeiosBlockTxsRequest db ebId bitmaps = do do let idxs = map fst bitmaps @@ -377,7 +421,7 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do -- -- TODO Better workaround for requests of many txs? stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (maxBatchSize `min` numOffsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegralEbId ebId) withDieMsg $ DB.exec db (fromString "BEGIN") acc <- (\f -> foldM f emptyX (batches offsets)) $ \acc batch -> do stmt <- @@ -385,7 +429,7 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do -- this can only be reached for the last batch withDie $ DB.finalize stmt_lookup_ebClosuresMAIN stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (numOffsets `mod` maxBatchSize) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegralEbId ebId) pure stmt_lookup_ebClosuresTIDY forM_ ([(2 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do withDie $ DB.bindInt64 stmt i (fromIntegral offset) @@ -408,14 +452,14 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak acc putStrLn "" -maxEbBodyByteSize :: Int -maxEbBodyByteSize = 500000 +maxEbBodyBytesSize :: Int +maxEbBodyBytesSize = 500000 -minEbItemByteSize :: Int -minEbItemByteSize = (1 + 32 + 1) + (1 + 1) +minEbItemBytesSize :: Int +minEbItemBytesSize = (1 + 32 + 1) + (1 + 1) maxEbItems :: Int -maxEbItems = (negate 1 + maxEbBodyByteSize - 1) `div` minEbItemByteSize +maxEbItems = (negate 1 + maxEbBodyBytesSize - 1) `div` minEbItemBytesSize {- | For example @ @@ -483,22 +527,25 @@ sql_lookup_ebClosures_DESC n = -- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlock -- -- PREREQ: No row in ebTxs already has this ebId. -msgLeiosBlock :: DB.Database -> Int -> Word64 -> FilePath -> IO () -msgLeiosBlock db ebId ebSlot ebPath = do +msgLeiosBlock :: DB.Database -> Word64 -> FilePath -> IO () +msgLeiosBlock db ebSlot ebPath = do ebBytes <- BS.readFile ebPath let ebHash :: Hash.Hash HASH ByteString ebHash = Hash.castHash $ Hash.hashWith id ebBytes + ebId <- do + dynEnv <- loadLeiosFetchDynEnvHelper False db + pure $ fst $ ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv stmt_write_ebIds <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) withDieMsg $ DB.exec db (fromString "BEGIN") -- INSERT INTO ebPoints withDie $ DB.bindInt64 stmt_write_ebIds 1 (fromIntegral ebSlot) withDie $ DB.bindBlob stmt_write_ebIds 2 (Hash.hashToBytes ebHash) - withDie $ DB.bindInt64 stmt_write_ebIds 3 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_write_ebIds 3 (fromIntegralEbId ebId) withDieDone $ DB.stepNoCB stmt_write_ebIds withDie $ DB.reset stmt_write_ebIds -- decode incrementally and simultaneously INSERT INTO ebTxs - withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegralEbId ebId) let decodeBreakOrEbPair = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> decodeEbPair @@ -506,10 +553,10 @@ msgLeiosBlock db ebId ebSlot ebPath = do (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrEbPair bytes go2 txOffset bytes' next go2 txOffset bytes = \case - Just (txHashBytes, txByteSize) -> do + Just (txHashBytes, txBytesSize) -> do withDie $ DB.bindInt64 stmt_write_ebBodies 2 txOffset withDie $ DB.bindBlob stmt_write_ebBodies 3 txHashBytes - withDie $ DB.bindInt64 stmt_write_ebBodies 4 (fromIntegral txByteSize) + withDie $ DB.bindInt64 stmt_write_ebBodies 4 (fromIntegral txBytesSize) withDieDone $ DB.stepNoCB stmt_write_ebBodies withDie $ DB.reset stmt_write_ebBodies go1 (txOffset + 1) bytes @@ -523,15 +570,24 @@ msgLeiosBlock db ebId ebSlot ebPath = do sql_insert_ebBody :: String sql_insert_ebBody = - "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txByteSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ + "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txBytesSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ \" -- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlockTxs -msgLeiosBlockTxs :: DB.Database -> Int -> FilePath -> [(Word16, Word64)] -> IO () -msgLeiosBlockTxs db ebId ebTxsPath bitmaps = do +msgLeiosBlockTxs :: DB.Database -> LeiosFetchDynamicEnv -> LeiosFetchState -> PeerId -> FilePath -> IO LeiosFetchState +msgLeiosBlockTxs db dynEnv lfst0 peerId ebTxsPath = do + (MkLeiosRequest ebSlot ebHash bitmaps0 txHashes, lfst1) <- + case Map.lookup peerId (requestedPerPeer lfst0) of + Just (req:reqs) -> pure $ (,) req $ lfst0 { + requestedPerPeer = + if null reqs then Map.delete peerId (requestedPerPeer lfst0) else + Map.insert peerId reqs (requestedPerPeer lfst0) + } + _ -> die "No such outstanding request" + let ebId = fst $ ebIdFromPoint ebSlot (let MkHashBytes x = ebHash in x) dynEnv ebTxsBytes <- BSL.readFile ebTxsPath stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) - withDie $ DB.bindInt64 stmt 2 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt 2 (fromIntegralEbId ebId) withDieMsg $ DB.exec db (fromString "BEGIN") -- decode incrementally and simultaneously UPDATE ebTxs -- @@ -539,33 +595,70 @@ msgLeiosBlockTxs db ebId ebTxsPath bitmaps = do let decodeBreakOrTx = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> CBOR.decodeBytes - let go1 offsets bytes = do + let go1 accRequested accTxBytesSize offsets bytes !i = do (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrTx bytes - go2 offsets bytes' next - go2 offsets bytes = \case - Just txBytes -> case offsets of - [] -> die "Too many txs" - txOffset:offsets' -> do + let txBytesSize = BSL.length bytes - BSL.length bytes' + txHash' :: Hash.Hash HASH ByteString + txHash' = Hash.hashWith id $ BSL.toStrict $ BSL.take txBytesSize bytes + go2 + accRequested + accTxBytesSize + offsets + bytes' + i + (fromIntegral txBytesSize) + txHash' + next + go2 accRequested accTxBytesSize offsets bytes !i txBytesSize txHash' = \case + Just txBytes -> case (offsets, txHashes V.!? i) of + ([], _) -> die "More txs than offsets" + (_, Nothing) -> die "More offsets than hashes" + + (txOffset:offsets', Just txHash) + | txHash /= MkHashBytes (Hash.hashToBytes txHash') -> die "Wrong tx hash" + | otherwise -> do withDie $ DB.bindInt64 stmt 3 $ fromIntegral txOffset withDie $ DB.bindBlob stmt 1 $ serialize' $ CBOR.encodeBytes txBytes withDieDone $ DB.stepNoCB stmt withDie $ DB.reset stmt - go1 offsets' bytes + let delIfNull x = if Set.null x then Nothing else Just x + go1 + (Map.update (delIfNull . Set.delete peerId) txHash accRequested) + (accTxBytesSize + txBytesSize) + offsets' + bytes + (i + 1) Nothing | not (BSL.null bytes) -> die "Incomplete EB txs decode" | txOffset:_ <- offsets -> die $ "Too few EB txs; next is " <> show txOffset - | otherwise -> pure () + | otherwise -> pure (accRequested, accTxBytesSize) let nextOffset = \case [] -> Nothing (idx, bitmap) : k -> case popLeftmostOffset bitmap of Nothing -> nextOffset k Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) - offsets = unfoldr nextOffset bitmaps + offsets0 = unfoldr nextOffset bitmaps0 (ebTxsBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeListLenIndef ebTxsBytes - go1 offsets ebTxsBytes2 + (requested', txBytesSize) <- go1 (requestedTxPeers lfst1) 0 offsets0 ebTxsBytes2 0 -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") + pure lfst1 { + requestedTxBytesSize = requestedTxBytesSize lfst1 - txBytesSize + , + requestedTxBytesSizePerPeer = + let delIfZero x = if 0 == x then Nothing else Just x + in + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIfZero $ x - txBytesSize + ) + peerId + (requestedTxBytesSizePerPeer lfst1) + , + requestedTxPeers = requested' + } sql_insert_ebTx :: String sql_insert_ebTx = @@ -576,30 +669,31 @@ sql_insert_ebTx = ----- +{- _maxTxOffsetBitWidth :: Int _maxTxOffsetBitWidth = ceiling $ log (fromIntegral maxEbItems :: Double) / log 2 maxRequestsPerIteration :: Int maxRequestsPerIteration = 10 -maxByteSizePerRequest :: Int -maxByteSizePerRequest = 500000 +maxBytesSizePerRequest :: Int +maxBytesSizePerRequest = 500000 fetchDecision :: DB.Database -> IntSet.IntSet -> IO () fetchDecision db ebIds = do stmt <- withDieJust $ DB.prepare db $ fromString $ sql_next_fetch (IntSet.size ebIds) forM_ ([(1 :: DB.ParamIndex) ..] `zip` IntSet.toDescList ebIds) $ \(i, p) -> do withDie $ DB.bindInt64 stmt i (fromIntegral p) - let loopLimit = maxRequestsPerIteration * maxByteSizePerRequest - loop !accReqs !accByteSize = - if accByteSize >= loopLimit then pure accReqs else + let loopLimit = maxRequestsPerIteration * maxBytesSizePerRequest + loop !accReqs !accBytesSize = + if accBytesSize >= loopLimit then pure accReqs else withDie (DB.stepNoCB stmt) >>= \case DB.Done -> pure accReqs DB.Row -> do ebId <- fromIntegral <$> DB.columnInt64 stmt 0 txOffset <- fromIntegral <$> DB.columnInt64 stmt 1 txHash <- DB.columnBlob stmt 2 - txByteSize <- fromIntegral <$> DB.columnInt64 stmt 3 + txBytesSize <- fromIntegral <$> DB.columnInt64 stmt 3 loop (IntMap.insertWith IntMap.union @@ -607,7 +701,7 @@ fetchDecision db ebIds = do (IntMap.singleton txOffset txHash) accReqs ) - (accByteSize + txByteSize) + (accBytesSize + txBytesSize) reqs <- loop IntMap.empty 0 forM_ (IntMap.assocs reqs) $ \(ebId, m) -> do let sho idx bitmap k = @@ -629,23 +723,16 @@ fetchDecision db ebIds = do $ unwords $ "hashes" : show ebId : map (BS8.unpack . BS16.encode) (IntMap.elems m) --- | Arbitrarily limited to 2000; about 2000 average txs are in the ball park --- of one megabyte. --- --- If a prefix of the 2000 txs are large, the fetch logic can ignore the rest. --- --- If all 2000 are still much less than a megabyte, then a) the EB is --- suspicious and b) the fetch logic can advance the query (TODO require --- parameterizing this query string with an OFFSET). +-- | The SQL query optimizer should use the @missingEbTxs@ INDEX. sql_next_fetch :: Int -> String sql_next_fetch n = - "SELECT ebId, txOffset, txHashBytes, txByteSize FROM ebTxs\n\ + "SELECT ebId, txOffset, txHashBytes, txBytesSize FROM ebTxs\n\ \WHERE txBytes IS NULL AND ebId IN (" ++ hooks ++ ")\n\ \ORDER BY ebId DESC, txOffset ASC\n\ - \LIMIT 2000\n\ \" where hooks = intercalate ", " (replicate n "?") +-} ----- @@ -671,3 +758,514 @@ hashTxs ebTxsPath = do die "Incomplete EB txs decode" (ebTxsBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeListLenIndef ebTxsBytes go1 ebTxsBytes2 + +----- + +newtype PeerId = MkPeerId String + deriving (Eq, Ord, Show) + deriving newtype (JSON.FromJSON, JSON.FromJSONKey, JSON.ToJSON, JSON.ToJSONKey) + +prettyPeerId :: PeerId -> String +prettyPeerId (MkPeerId x) = x + +newtype EbId = MkEbId Int + deriving (Eq, Ord, Show) + deriving newtype (JSON.FromJSON, JSON.FromJSONKey, JSON.ToJSON, JSON.ToJSONKey) + +prettyEbId :: EbId -> String +prettyEbId (MkEbId y) = show y + +fromIntegralEbId :: Integral a => EbId -> a +fromIntegralEbId (MkEbId y) = fromIntegral y + +newtype HashBytes = MkHashBytes ByteString + deriving (Eq, Ord, Show) + +prettyHashBytes :: HashBytes -> String +prettyHashBytes (MkHashBytes bytes) = BS8.unpack $ BS16.encode bytes + +hashBytesToText :: HashBytes -> T.Text +hashBytesToText (MkHashBytes hash) = + let hex = BS16.encode hash + in + case T.decodeUtf8' hex of + Left err -> error $ "bad HashBytes, " <> show err <> ": " <> BS8.unpack hex + Right txt -> txt + +instance JSON.FromJSON HashBytes where + parseJSON val = do + txt <- JSON.parseJSON val + case BS16.decode $ T.encodeUtf8 txt of + Left s -> error $ "bad HashBytes, " <> s <> ": " <> T.unpack txt + Right b -> pure $ MkHashBytes b + +instance JSON.FromJSONKey HashBytes where + fromJSONKey = + JSON.FromJSONKeyTextParser $ \txt -> + case BS16.decode $ T.encodeUtf8 txt of + Left s -> error $ "bad HashBytes, " <> s <> ": " <> T.unpack txt + Right b -> pure $ MkHashBytes b + +instance JSON.ToJSON HashBytes where + toJSON = JSON.toJSON . hashBytesToText + toEncoding = JSON.toEncoding . hashBytesToText + +instance JSON.ToJSONKey HashBytes where + toJSONKey = hashBytesToText >$< JSON.toJSONKey + +-- | INVARIANT: no overlap +data LeiosFetchState = MkLeiosFetchState { + -- | Which EBs each peer has offered the closure for + -- + -- INVARIANT: every set of EBs all exactly agree about the claimed size of each tx + -- + -- TODO reverse index for when EBs age out? + offeredEbTxs :: Map PeerId (Set EbId) + , + -- | Which requests have actually been sent to this peer + requestedPerPeer :: Map PeerId [LeiosRequest] + , + -- | INVARIANT: no empty sets + -- + -- INVARIANT: @<= maxRequestedTxBytes@ + -- + -- TODO may need to also store priority here + requestedTxPeers :: Map TxHash (Set PeerId) + , + -- | Outstanding requested 'TxBytesSize' for each peer + -- + -- INVARIANT: @Map.all (<= maxRequestedTxBytesPerPeer)@ + requestedTxBytesSizePerPeer :: Map PeerId TxBytesSize + , + -- | Sum of 'requestedTxBytesSizePerPeer' + -- + -- INVARIANT: @<= maxRequestedTxBytes@ + requestedTxBytesSize :: TxBytesSize + } + deriving (Generic) + +-- | defaults to @GHC.Generics@ +instance JSON.FromJSON LeiosFetchState where {} + +-- | defaults to @GHC.Generics@ +instance JSON.ToJSON LeiosFetchState where {} + +emptyLeiosFetchState :: LeiosFetchState +emptyLeiosFetchState = + MkLeiosFetchState + Map.empty + Map.empty + Map.empty + Map.empty + 0 + +ebIdSlot :: EbId -> Word64 +ebIdSlot (MkEbId y) = + fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64 + +ebIdToPoint :: EbId -> LeiosFetchDynamicEnv -> Maybe (Word64, ByteString) +ebIdToPoint (MkEbId y) x = + f <$> IntMap.lookup y (ebPointsInverse x) + where + f (MkHashBytes z) = (ebIdSlot (MkEbId y), z) + +ebIdFromPoint :: Word64 -> ByteString -> LeiosFetchDynamicEnv -> (EbId, LeiosFetchDynamicEnv) +ebIdFromPoint slotNo hash x = + case IntMap.lookup (fromIntegral slotNo) (ebPoints x) of + Just m -> case Map.lookup hashBytes m of + Just y -> (y, x) + Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) - Map.size m + Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) + where + hashBytes = MkHashBytes hash + + zero = fromIntegral ((slotNo `Bits.unsafeShiftL` 20) :: Word64) + minBound :: Int + + gen y = + (,) y + $ x { ebPoints = IntMap.insertWith Map.union (fromIntegral slotNo) (Map.singleton hashBytes y) (ebPoints x) + , ebPointsInverse = let MkEbId z = y in IntMap.insert z hashBytes (ebPointsInverse x) + } + +----- + +type TxBytesSize = Int + +type TxHash = HashBytes + +data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv + { + -- | At most this many outstanding bytes requested from all peers together + maxRequestedTxBytes :: TxBytesSize + , + -- | At most this many outstanding bytes requested from each peer + maxRequestedTxBytesPerPeer :: TxBytesSize + , + -- | At most this many outstanding bytes per request + maxRequestTxBytesSize :: TxBytesSize + , + -- | At most this many outstanding requests for each individual tx + maxRequestsPerTx :: Int + } + +-- TODO these maps are too big to actually have on the heap in the worst-case: +-- 13888 txs per EB, 11000 EBs, 50 upstream peers, 32 bytes per hash +data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv + { + -- | @slot -> hash -> EbId@ + -- + -- This relation is written to and loaded from the 'ebPoints' table on node + -- shutdown and startup. + -- + -- INVARIANT: the inner map is non-empty + -- + -- INVARIANT: strictly ascending 'EbId's, which is ensured as follows. + -- + -- Assumptions: + -- o This code base will not survive more than 100 years. + -- o The EBs' slot schedule will never be more granular than 5000 per second. + -- o There will be never be more than 2^20 elections in a single EB slot. + -- + -- Therefore, since 2^(64 - 20) = 2^44 seconds is more than 500,000 years, + -- the 20 highest-order bits of the slot number will be 0 for the entire + -- lifetime of this codebase, and so can be repurposed to identify + -- individual EBs. + -- + -- PREREQ: As justified above, this codes assumes the slot number will + -- never exceed 2^44 - 1. + -- + -- Thus, the first EB with slot S received is assigned 'EbId' @fromIntegral + -- (S << 20) + 2^20 - 1 + minBound@, the next EB with slot S to arrive is + -- assigned the predecessor (so the tiebreaker favors first to arrive), and + -- so on. Note that @(enm () :: [Int]) == map cnv (enm () :: [Word64])@ + -- where @cnv w = fromIntegral (w :: Word64) + minBound :: Int@ and @enm () + -- = [minBound, minBound + 1, maxBound - 1, maxBound]@. + ebPoints :: IntMap {- SlotNo -} (Map HashBytes EbId) + , + -- | Reverse index of 'ebPoints', just the hash + -- + -- INVARIANT: @(ebPoints IntMap.! (ebIdSlot ebId)) Map.! (ebPointsInverse IntMap.! ebId) = ebId@ + ebPointsInverse :: IntMap {- EbId -} HashBytes + , +-- acquiredTxBodies :: Map TxHash TxBytes +-- , + -- | Txs listed in received EBs but never themselves received + missingTxBodies :: Set TxHash + , + -- | All missing txs in the context of EBs worth retrieving the closure for + ebBodies :: Map EbId (IntMap (TxHash, TxBytesSize)) + , + -- | Reverse index of 'ebBodies' + -- + -- INVARIANT: @let (ebId, txOffset) = txOffsetss Map.! h in h = fst ((ebBodies IntMap.! ebId) IntMap.! txOffset)@ + txOffsetss :: Map TxHash (Map EbId Int) + } + +emptyLeiosFetchDynEnv :: LeiosFetchDynamicEnv +emptyLeiosFetchDynEnv = + MkLeiosFetchDynamicEnv + IntMap.empty + IntMap.empty + Set.empty + Map.empty + Map.empty + +loadLeiosFetchDynEnv :: DB.Database -> IO LeiosFetchDynamicEnv +loadLeiosFetchDynEnv = loadLeiosFetchDynEnvHelper True + +loadLeiosFetchDynEnvHelper :: Bool -> DB.Database -> IO LeiosFetchDynamicEnv +loadLeiosFetchDynEnvHelper full db = do + (ps, qs) <- do + stmt <- withDieJust $ DB.prepare db (fromString sql_scan_ebId) + let loop !ps !qs = + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> pure (ps, qs) + DB.Row -> do + ebSlot <- fromIntegral <$> DB.columnInt64 stmt 0 + ebHash <- MkHashBytes <$> DB.columnBlob stmt 1 + ebId <- fromIntegral <$> DB.columnInt64 stmt 2 + loop + (IntMap.insertWith Map.union ebSlot (Map.singleton ebHash (MkEbId ebId)) ps) + (IntMap.insert ebId ebHash qs) + loop IntMap.empty IntMap.empty + (missing, bodies, offsetss) <- if not full then pure (Set.empty, Map.empty, Map.empty) else do + stmt <- withDieJust $ DB.prepare db (fromString sql_scan_missingEbTx) + let loop !missing !bodies !offsetss = + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> pure (missing, bodies, offsetss) + DB.Row -> do + ebId <- (MkEbId . fromIntegral) <$> DB.columnInt64 stmt 0 + txOffset <- fromIntegral <$> DB.columnInt64 stmt 1 + txHash <- MkHashBytes <$> DB.columnBlob stmt 2 + txBytesSize <- fromIntegral <$> DB.columnInt64 stmt 3 + loop + (Set.insert txHash missing) + (Map.insertWith IntMap.union ebId (IntMap.singleton txOffset (txHash, txBytesSize)) bodies) + (Map.insertWith Map.union txHash (Map.singleton ebId txOffset) offsetss) + loop Set.empty Map.empty Map.empty + pure MkLeiosFetchDynamicEnv + { + ebPoints = ps + , + ebPointsInverse = qs + , + missingTxBodies = missing + , + ebBodies = bodies + , + txOffsetss = offsetss + } + +sql_scan_ebId :: String +sql_scan_ebId = + "SELECT ebSlot, ebHash, ebId\n\ + \FROM ebPoints\n\ + \ORDER BY ebId ASC\n\ + \" + +sql_scan_missingEbTx :: String +sql_scan_missingEbTx = + "SELECT ebId, txOffset, txHashBytes, txBytesSize\n\ + \FROM ebTxs\n\ + \WHERE txBytes IS NULL\n\ + \ORDER BY ebId DESC, txOffset ASC\n\ + \" + +----- + +newtype LeiosRequestDecisions = + MkLeiosRequestDecisions + (Map PeerId (Map Word64 (DList (TxHash, TxBytesSize, Map EbId Int)))) + deriving (Show) + +leiosFetchLogicIteration :: + LeiosFetchStaticEnv + -> + LeiosFetchDynamicEnv + -> + LeiosFetchState + -> + (LeiosFetchState, LeiosRequestDecisions) +leiosFetchLogicIteration env dynEnv = + \acc -> + go1 acc (MkLeiosRequestDecisions Map.empty) + $ expand + $ Map.toDescList + $ ebBodies dynEnv + where + expand = \case + [] -> [] + (ebId, v):vs -> + [ (ebId, txHash) | (txHash, _txBytesSize) <- IntMap.elems v ] + <> expand vs + go1 !acc !accNew = \case + [] + -> (acc, accNew) + + (ebId, txHash):txHashes + + | Set.member txHash (missingTxBodies dynEnv) -- we don't already have it + , let !txOffsets = case Map.lookup txHash (txOffsetss dynEnv) of + Nothing -> error "impossible!" + Just x -> x + , let peerIds :: Set PeerId + !peerIds = Map.findWithDefault Set.empty txHash (requestedTxPeers acc) + -> go2 acc accNew txHashes (ebIdSlot ebId) txHash txOffsets peerIds + + | otherwise + -> go1 acc accNew txHashes + + go2 !acc !accNew txHashes ebSlot txHash txOffsets peerIds + + | requestedTxBytesSize acc >= maxRequestedTxBytes env -- we can't request anything + = (acc, accNew) + + | Set.size peerIds < maxRequestsPerTx env -- we would like to request it from an additional peer + -- TODO if requests list priority, does this limit apply even if the + -- tx has only been requested at lower priorities? + , Just (peerId, txOffsets') <- choosePeer peerIds acc txOffsets + -- there's a peer who offered it and we haven't already requested it from them + = let txBytesSize = case Map.lookupMax txOffsets' of + Nothing -> error "impossible!" + Just (ebId, txOffset) -> case Map.lookup ebId (ebBodies dynEnv) of + Nothing -> error "impossible!" + Just v -> snd $ v IntMap.! txOffset + accNew' = + MkLeiosRequestDecisions + $ Map.insertWith + (Map.unionWith (<>)) + peerId + (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'))) + (let MkLeiosRequestDecisions x = accNew in x) + acc' = MkLeiosFetchState { + offeredEbTxs = offeredEbTxs acc + , + requestedPerPeer = requestedPerPeer acc + , + requestedTxPeers = Map.insertWith Set.union txHash (Set.singleton peerId) (requestedTxPeers acc) + , + requestedTxBytesSizePerPeer = Map.insertWith (+) peerId txBytesSize (requestedTxBytesSizePerPeer acc) + , + requestedTxBytesSize = txBytesSize + requestedTxBytesSize acc + } + peerIds' = Set.insert peerId peerIds + in + go2 acc' accNew' txHashes ebSlot txHash txOffsets peerIds' + + | otherwise + = go1 acc accNew txHashes + + choosePeer :: Set PeerId -> LeiosFetchState -> Map EbId Int -> Maybe (PeerId, Map EbId Int) + choosePeer peerIds acc txOffsets = + foldr (\a _ -> Just a) Nothing + $ [ (peerId, txOffsets') + | (peerId, ebIds) <- + Map.toList -- TODO prioritize/shuffle? + $ (`Map.withoutKeys` peerIds) -- not already requested from this peer + $ offeredEbTxs acc + , Map.findWithDefault 0 peerId (requestedTxBytesSizePerPeer acc) <= maxRequestedTxBytesPerPeer env + -- peer can be sent more requests + , let txOffsets' = txOffsets `Map.restrictKeys` ebIds + , not $ Map.null txOffsets' -- peer has offered an EB closure that includes this tx + ] + +----- + +data LeiosRequest = + -- | ebSlot, ebHash, bitmaps, txHashes + -- + -- The hashes aren't sent to the peer, but they are used to validate the + -- reply when it arrives. + MkLeiosRequest + !Word64 + !HashBytes + [(Word16, Word64)] + !(V.Vector TxHash) + deriving (Generic, Show) + +-- | defaults to @GHC.Generics@ +instance JSON.FromJSON LeiosRequest where {} + +-- | defaults to @GHC.Generics@ +instance JSON.ToJSON LeiosRequest where {} + +packRequests :: LeiosFetchStaticEnv -> LeiosFetchDynamicEnv -> LeiosRequestDecisions -> Map PeerId [LeiosRequest] +packRequests env dynEnv = + \(MkLeiosRequestDecisions x) -> Map.map goPeer x + where + goPeer = + DList.toList + . Map.foldlWithKey + (\acc prio txs -> goPrio prio txs <> acc) + DList.empty + + goPrio _prio txs = + Map.foldlWithKey + (\acc ebId txs' -> + case ebIdToPoint ebId dynEnv of + Nothing -> error "impossible!" + Just (ebSlot, ebHash) -> + goEb + {- prio -} + ebSlot ebHash + 0 + IntMap.empty + 0 + DList.empty + (IntMap.toAscList txs') + <> acc + ) + DList.empty + -- group by EbId, sort by offset ascending + $ Map.fromListWith IntMap.union + $ [ (,) ebId $ IntMap.singleton txOffset (txHash, txBytesSize) + | (txHash, txBytesSize, txOffsets) <- DList.toList txs + -- TODO somewhat arbitrarily choosing the freshest EbId here; merely + -- something simple and sufficient for the demo + , let (ebId, txOffset) = + case Map.lookupMax txOffsets of + Nothing -> error "impossible!" + Just x -> x + ] + + goEb :: + Word64 + -> + ByteString + -> + TxBytesSize + -> + IntMap Word64 + -> + Int + -> + DList TxHash + -> + [(Int, (TxHash, TxBytesSize))] + -> + DList LeiosRequest + -- TODO the incoming indexes are ascending, so the IntMap accumulator could + -- be simplified away + goEb ebSlot ebHash !accTxBytesSize !accBitmaps !accN !accHashes = \case + [] -> if 0 < accN then DList.singleton flush else DList.empty + (txOffset, (txHash, txBytesSize)):txs + + | maxRequestTxBytesSize env < accTxBytesSize' + -> flush `DList.cons` goEb ebSlot ebHash 0 IntMap.empty 0 DList.empty txs + + | otherwise + , let (q, r) = txOffset `divMod` 64 + -> goEb + ebSlot ebHash + accTxBytesSize' + (IntMap.insertWith (Bits..|.) q (Bits.bit (63 - r)) accBitmaps) + (accN + 1) + (accHashes `DList.snoc` txHash) + txs + + where + accTxBytesSize' = accTxBytesSize + txBytesSize + + where + flush = + MkLeiosRequest + {- prio -} + ebSlot + (MkHashBytes ebHash) + [ (fromIntegral idx, bitmap) | (idx, bitmap) <- IntMap.toAscList accBitmaps ] + (V.fromListN accN $ DList.toList accHashes) + +----- + +fetchDecision2 :: DB.Database -> LeiosFetchState -> IO LeiosFetchState +fetchDecision2 db acc0 = do + let env = MkLeiosFetchStaticEnv + { + maxRequestedTxBytes = 50 * 10^(6 :: Int) + , + maxRequestedTxBytesPerPeer = 5 * 10^(6 :: Int) + , + maxRequestTxBytesSize = 500000 + , + maxRequestsPerTx = 2 + } + dynEnv <- loadLeiosFetchDynEnv db + let (acc1, MkLeiosRequestDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 + forM_ (Map.toList decisions) $ \(peerId, slots) -> do + forM_ (Map.toDescList slots) $ \(slot, dlist) -> do + forM_ dlist $ \(txHash, _txBytesSize, ebIds) -> do + putStrLn $ unwords $ "TX" : prettyPeerId peerId : show slot : prettyHashBytes txHash : [ prettyEbId ebId ++ "~" ++ show txOffset | (ebId, txOffset) <- Map.toList ebIds ] + acc2 <- (\f -> foldM f acc1 (Map.toList $ packRequests env dynEnv (MkLeiosRequestDecisions decisions))) $ \acc (peerId, reqs) -> do + forM_ reqs $ \req -> do + let MkLeiosRequest ebSlot ebHash bitmaps _txHashes = req + putStrLn $ unwords $ "MSG" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps + pure $ acc { requestedPerPeer = Map.insertWith (\new old -> old ++ new) peerId reqs (requestedPerPeer acc) } + pure acc2 + +----- + +msgLeiosBlockTxsOffer :: LeiosFetchState -> PeerId -> [EbId] -> IO LeiosFetchState +msgLeiosBlockTxsOffer acc peerId ebIds = do + pure acc { + offeredEbTxs = Map.insertWith Set.union peerId (Set.fromList ebIds) (offeredEbTxs acc) + } diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index b0b6189e7b..21aa1aed28 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -865,5 +865,8 @@ executable leiosdemo202510 containers, direct-sqlite, directory, + dlist, + ghc-prim, random, + text, vector, From fb926415f332eb4dbf8b291039291c1b0d672585 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 22 Oct 2025 11:40:52 -0700 Subject: [PATCH 040/119] leiosdemo202510: add the first bash script that mimics requests and replies --- leiosdemo202510-first-script | 40 ++++++++++++++++++++++++++++++++++++ myManifest.json | 37 +++++++++++++++++++++++++++++++++ 2 files changed, 77 insertions(+) create mode 100755 leiosdemo202510-first-script create mode 100644 myManifest.json diff --git a/leiosdemo202510-first-script b/leiosdemo202510-first-script new file mode 100755 index 0000000000..c970c67669 --- /dev/null +++ b/leiosdemo202510-first-script @@ -0,0 +1,40 @@ +#! /bin/bash +rm -f tmp/my.db tmp/up.db tmp/my.lfst tmp/demo tmp/reqs +set -eux +cabal build exe:leiosdemo202510 +ln -s $(cabal list-bin exe:leiosdemo202510) tmp/demo +tmp/demo generate tmp/up.db tmp/my.lfst tmp/myManifest.json +cp tmp/{up,my}.db +sqlite3 tmp/my.db "SELECT ebSlot, PRINTF('%X', ebId), ebId FROM ebPoints ORDER BY ebId ASC" # dump points +sqlite3 tmp/my.db 'SELECT ebId, MAX(txOffset) FROM ebTxs GROUP BY ebId' # dump sizes +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +sqlite3 tmp/my.db 'UPDATE ebTxs SET txBytes = NULL WHERE ebId = -9223372036843241473' +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo MsgLeiosBlockTxsOffer tmp/my.lfst Alice -9223372036848484353 -9223372036843241473 +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo MsgLeiosBlockTxsOffer tmp/my.lfst Bob -9223372036848484353 -9223372036843241473 +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +sqlite3 tmp/my.db 'UPDATE ebTxs SET txBytes = NULL WHERE ebId = -9223372036848484353' +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +jq . tmp/my.lfst +sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +set +x +cat tmp/reqs | grep -e MSG | grep -e Alice | cut -d' ' -f3- | while IFS= read -r line; do + set -x + tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Alice tmp/foo.bin + set +x + jq . tmp/my.lfst + sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +done +cat tmp/reqs | grep -e MSG | grep -e Bob | cut -d' ' -f3- | while IFS= read -r line; do + set -x + tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Bob tmp/foo.bin + jq . tmp/my.lfst + sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes + set +x +done diff --git a/myManifest.json b/myManifest.json new file mode 100644 index 0000000000..cb61492f43 --- /dev/null +++ b/myManifest.json @@ -0,0 +1,37 @@ +[ + {"slotNo": 5, "txBytesSizes": [55, 55, 55, 1000]} + , + {"slotNo": 10, "txBytesSizes": [100, 200, 300]} + , + {"slotNo": 15, "comment": "closure = 12.5 megabyte, minimal EB", "txBytesSizes": + [15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] + } + , + {"slotNo": 20, "comment": "closure = 12.5 megabyte, maximal EB under 0.5 megabyte", "txBytesSizes": + [1398, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925] + } + , + {"slotNo": 100, "txBytesSizes": [55]} + , + {"slotNo": 100, "txBytesSizes": [255]} + , + {"slotNo": 100, "txBytesSizes": [925]} + , + {"slotNo": 100, "txBytesSizes": [16384]} +] From ba40262dd30aa3c81c155933e55f99b876462e9d Mon Sep 17 00:00:00 2001 From: dnadales Date: Wed, 22 Oct 2025 17:18:10 -0300 Subject: [PATCH 041/119] Implement mkGetSlotDelay --- .../app/immdb-server.hs | 36 +++++++++++++++++-- scripts/leios-demo/leios-october-demo.sh | 7 ++-- 2 files changed, 38 insertions(+), 5 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index 2b8e0c4ba5..ad29fa6a37 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -1,4 +1,5 @@ {-# LANGUAGE ApplicativeDo #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} module Main (main) where @@ -12,8 +13,10 @@ import Main.Utf8 (withStdTerminalHandles) import qualified Network.Socket as Socket import Options.Applicative import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) -import Cardano.Slotting.Slot (SlotNo (..)) +import Cardano.Slotting.Slot (SlotNo (..), WithOrigin (At, Origin)) import qualified Data.Time.Clock.POSIX as POSIX +import Data.Time.Clock (DiffTime) +import Data.Int (Int64) main :: IO () main = withStdTerminalHandles $ do @@ -31,7 +34,31 @@ main = withStdTerminalHandles $ do pInfoConfig (mkGetSlotDelay refSlotNr refTimeForRefSlot) where - mkGetSlotDelay = undefined + -- NB we assume for now the slot duration is 1 second. + -- + -- If we want to this in the actual chain we will need to access + -- the information from the configuration file to run the + -- Qry.slotToWallclock query. + mkGetSlotDelay :: SlotNo -> POSIX.POSIXTime -> WithOrigin SlotNo -> IO DiffTime + mkGetSlotDelay refSlotNr refTimeForRefSlot = + -- If slot < refSlotNr, we need to subtract to + -- refTimeForRefSlot. To simplify the calculations we work + -- with Int64 + let iRefSlotNr :: Int64 + iRefSlotNr = fromIntegral $ unSlotNo refSlotNr + + -- TODO: here is where we assume the slot duration of 1 second. + toSeconds :: Int64 -> POSIX.POSIXTime + toSeconds iSlot = realToFrac iSlot + in \case Origin -> pure 0 -- TODO: I'm not sure what we want to do here. + At slot -> do + let iSlot = fromIntegral $ unSlotNo slot + slotTime = refTimeForRefSlot + toSeconds (iSlot - iRefSlotNr) + + currentTime <- POSIX.getPOSIXTime + pure $ if currentTime <= slotTime + then realToFrac $ slotTime - currentTime + else 0 data Opts = Opts { immDBDir :: FilePath @@ -74,9 +101,12 @@ optsParser = , help "Reference slot number (SlotNo). This, together with the initial-time will be used for time translations." , metavar "SLOT_NO" ] - refTimeForRefSlot <- option auto $ mconcat + refTimeForRefSlot <- fmap asPOSIXseconds $ option auto $ mconcat [ long "initial-time" , help "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)" , metavar "POSIX_SECONDS" ] pure Opts {immDBDir, port, configFile, refSlotNr, refTimeForRefSlot} + where + asPOSIXseconds :: Double -> POSIX.POSIXTime + asPOSIXseconds = realToFrac diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 23f66c7927..e1bf1880ed 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -125,11 +125,14 @@ popd > /dev/null ## ## TODO: we should find a better way to wait for the nodes to be started -sleep 30 +# Calculate the POSIX time 60 seconds from now. +REF_TIME_FOR_SLOT=$(( $(date +%s) + 60 )) IMMDB_CMD_CORE="cabal run immdb-server \ -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ - --config $CLUSTER_RUN_DATA/node-0/config.json" + --config $CLUSTER_RUN_DATA/node-0/config.json \ + --initial-slot 80 \ + --initial-time $REF_TIME_FOR_SLOT" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" From 02dc37eeee395308804e78836a7068eef2f4bf4b Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 22 Oct 2025 13:11:36 -0700 Subject: [PATCH 042/119] leiosdemo202510: add tx sharing to the generator --- myManifest.json | 64 +++++++---- ouroboros-consensus/app/leiosdemo202510.hs | 119 ++++++++++++++++----- 2 files changed, 133 insertions(+), 50 deletions(-) diff --git a/myManifest.json b/myManifest.json index cb61492f43..a7e48099e3 100644 --- a/myManifest.json +++ b/myManifest.json @@ -1,37 +1,55 @@ [ - {"slotNo": 5, "txBytesSizes": [55, 55, 55, 1000]} + {"slotNo": 5, "txRecipes": [55, 55, 55, 1000]} , - {"slotNo": 10, "txBytesSizes": [100, 200, 300]} + {"slotNo": 10, "binder": "SmallA", "txRecipes": [100, 200, 300]} , - {"slotNo": 15, "comment": "closure = 12.5 megabyte, minimal EB", "txBytesSizes": - [15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] + {"slotNo": 11, "txRecipes": [{"share": "SmallA", "startIncl": 0}, 400]} + , + {"slotNo": 15, "comment": "closure = 12.5 megabyte, minimal EB", "txRecipes": + [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } , - {"slotNo": 20, "comment": "closure = 12.5 megabyte, maximal EB under 0.5 megabyte", "txBytesSizes": - [1398, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + {"slotNo": 20, "binder": "BigA", "comment": "closure = 12.5 megabyte, maximal EB under 0.5 megabyte", "txRecipes": + [ 1398, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, - 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925] + 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925 + ] } , - {"slotNo": 100, "txBytesSizes": [55]} + {"slotNo": 21, "comment": "a slightly scrambled suffix of BigA, plus some more", "txRecipes": + [ {"share": "BigA", "startIncl": 90, "stopExcl": 105}, + {"share": "BigA", "startIncl": 80, "stopExcl": 90}, + {"share": "BigA", "startIncl": 105}, + + 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, + 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, + 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, + 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, + 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000, 1000 + ] + } + , + {"slotNo": 100, "txRecipes": [55]} + , + {"slotNo": 100, "txRecipes": [255]} , - {"slotNo": 100, "txBytesSizes": [255]} + {"slotNo": 100, "txRecipes": [925]} , - {"slotNo": 100, "txBytesSizes": [925]} + {"slotNo": 100, "txRecipes": [1000]} , - {"slotNo": 100, "txBytesSizes": [16384]} + {"slotNo": 100, "txRecipes": [16384]} ] diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index c40c6ab655..6aa5494ccb 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -15,6 +15,7 @@ import qualified Cardano.Crypto.Hash as Hash import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR +import Control.Applicative ((<|>)) import Control.Monad (foldM, when) import qualified Data.Aeson as JSON import qualified Data.Bits as Bits @@ -26,11 +27,13 @@ import qualified Data.ByteString.Lazy as BSL import Data.DList (DList) import qualified Data.DList as DList import Data.Foldable (forM_) +import qualified Data.Foldable as Foldable import Data.Functor.Contravariant ((>$<)) import qualified Data.IntMap as IntMap import Data.IntMap (IntMap) import Data.List (intercalate, isSuffixOf, unfoldr) import Data.Map (Map) +import Data.Maybe (fromMaybe) import qualified Data.Map as Map import Data.Set (Set) import qualified Data.Set as Set @@ -155,16 +158,36 @@ prettyBitmap (idx, bitmap) = show idx ++ ":0x" ++ Numeric.showHex bitmap "" data EbRecipe = EbRecipe { - ebRecipeSlotNo :: Word64 + ebRecipeBinder :: Maybe String + , + ebRecipeElems :: V.Vector EbRecipeElem , - ebRecipeTxBytesSizes :: V.Vector Word16 + ebRecipeSlotNo :: Word64 } - deriving (Generic, Show) + deriving (Show) instance JSON.FromJSON EbRecipe where parseJSON = JSON.withObject "EbRecipe" $ \v -> EbRecipe - <$> v JSON..: (fromString "slotNo") - <*> v JSON..: (fromString "txBytesSizes") + <$> v JSON..:? (fromString "binder") + <*> v JSON..: (fromString "txRecipes") + <*> v JSON..: (fromString "slotNo") + +data EbRecipeElem = + EbRecipeTxBytesSize Word16 + | + -- | Binder occurrence, inclusive start, and exclusive stop + EbRecipeShare String Int (Maybe Int) + deriving (Show) + +instance JSON.FromJSON EbRecipeElem where + parseJSON = + \v -> size v <|> share v + where + size v = EbRecipeTxBytesSize <$> JSON.parseJSON @Word16 v + share = JSON.withObject "EbRecipeElem" $ \v -> EbRecipeShare + <$> v JSON..: (fromString "share") + <*> v JSON..: (fromString "startIncl") + <*> v JSON..:? (fromString "stopExcl") ----- @@ -178,32 +201,62 @@ generateDb prng0 db ebRecipes = do stmt_write_ebId <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) - _dynEnv' <- (\f -> foldM f emptyLeiosFetchDynEnv ebRecipes) $ \dynEnv ebRecipe -> do + (_dynEnv', _sigma) <- (\f -> foldM f (emptyLeiosFetchDynEnv, Map.empty) ebRecipes) $ \(dynEnv, sigma) ebRecipe -> do -- generate txs, so we have their hashes - txs <- V.forM (ebRecipeTxBytesSizes ebRecipe) $ \txBytesSize -> do - -- generate a random bytestring whose CBOR encoding has the expected length - -- - -- In the actual implementation, the values themselves will be - -- valid CBOR. It's useful to maintain that invariant even for the - -- otherwise-opaque random data within this prototype/demo. - when (txBytesSize < 55) $ die "Tx cannot be smaller than 55 bytes" - let overhead -- one for the initial byte, plus 1 2 4 or 8 for the length argument - | txBytesSize < fromIntegral (maxBound :: Word8) = 2 - | txBytesSize < (maxBound :: Word16) = 3 - | txBytesSize < fromIntegral (maxBound :: Word32) = 5 - | otherwise = 9 - txBytes <- id - $ fmap (serialize' . CBOR.encodeBytes) - $ R.uniformByteStringM (fromIntegral txBytesSize - overhead) gref - pure (txBytes, Hash.hashWith id txBytes :: Hash.Hash HASH ByteString) + let finishX (n, x) = V.fromListN n $ Foldable.toList $ revX x -- TODO in ST with mut vector + txs <- fmap finishX $ (\f -> V.foldM f (0, emptyX) (ebRecipeElems ebRecipe)) $ \(accN, accX) -> \case + EbRecipeShare occ startIncl mbStopExcl -> do + (srcEbId, ebTxsCount) <- case Map.lookup occ sigma of + Nothing -> die $ "Could not find EB binder: " ++ occ + Just x -> pure x + let stopExcl = fromMaybe ebTxsCount mbStopExcl + len = stopExcl - startIncl + when (len < 0) $ die $ "Non-positive share length: " ++ show (occ, startIncl, mbStopExcl, stopExcl, len) + -- SELECT the referenced txs + stmt <- withDieJust $ DB.prepare db (fromString sql_share_ebClosures_ASC) + withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId srcEbId) + withDie $ DB.bindInt64 stmt 2 (fromIntegral startIncl) + withDie $ DB.bindInt64 stmt 3 (fromIntegral len) + let loop i !accX' = + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> do + when (i /= fromIntegral stopExcl) $ do + die $ "Ran out of txs for share" ++ show (occ, startIncl, mbStopExcl, i) + pure accX' + DB.Row -> do + txOffset <- DB.columnInt64 stmt 0 + txHashBytes <- DB.columnBlob stmt 1 + txBytes <- DB.columnBlob stmt 2 + when (txOffset /= i) $ do + die $ "Unexpected share txOffset" ++ show (occ, startIncl, mbStopExcl, txOffset, i) + loop (i + 1) $ pushX accX' (txBytes, MkHashBytes txHashBytes) + accX' <- loop (fromIntegral startIncl) accX + pure (accN + len, accX') + EbRecipeTxBytesSize txBytesSize -> do + -- generate a random bytestring whose CBOR encoding has the expected length + -- + -- In the actual implementation, the values themselves will be + -- valid CBOR. It's useful to maintain that invariant even for + -- the otherwise-opaque random data within this prototype/demo. + when (txBytesSize < 55) $ die "Tx cannot be smaller than 55 bytes" + when (txBytesSize > 2^(14::Int)) $ die "Tx cannot be be larger than 2^14 bytes" + let overhead -- one for the initial byte, plus 1 2 4 or 8 for the length argument + | txBytesSize < fromIntegral (maxBound :: Word8) = 2 + | txBytesSize < (maxBound :: Word16) = 3 + | txBytesSize < fromIntegral (maxBound :: Word32) = 5 + | otherwise = 9 + txBytes <- id + $ fmap (serialize' . CBOR.encodeBytes) + $ R.uniformByteStringM (fromIntegral txBytesSize - overhead) gref + let txHash = Hash.hashWith id txBytes :: Hash.Hash HASH ByteString + pure (accN + 1, accX `pushX` (txBytes, MkHashBytes $ Hash.hashToBytes txHash)) let ebSlot = ebRecipeSlotNo ebRecipe let ebHash :: Hash.Hash HASH ByteString ebHash = Hash.castHash $ Hash.hashWithSerialiser - (encodeEB (fromIntegral . BS.length) Hash.hashToBytes) + (encodeEB (fromIntegral . BS.length) (\(MkHashBytes x) -> x)) txs - let (ebId, dynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv withDieMsg $ DB.exec db (fromString "BEGIN") withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegralEbId ebId) @@ -217,16 +270,17 @@ generateDb prng0 db ebRecipes = do V.iforM_ txs $ \txOffset (txBytes, txHash) -> do -- INSERT INTO ebTxs withDie $ DB.bindInt64 stmt_write_ebClosure 2 (fromIntegral txOffset) - withDie $ DB.bindBlob stmt_write_ebClosure 3 (Hash.hashToBytes txHash) + withDie $ DB.bindBlob stmt_write_ebClosure 3 (let MkHashBytes x = txHash in x) withDie $ DB.bindInt64 stmt_write_ebClosure 4 (fromIntegral (BS.length txBytes)) withDie $ DB.bindBlob stmt_write_ebClosure 5 txBytes withDieDone $ DB.stepNoCB stmt_write_ebClosure withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") - pure dynEnv' + pure (dynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeBinder ebRecipe) sigma) -- finalize db withDieMsg $ DB.exec db (fromString sql_index_schema) + -- TODO maybe print out the @sigma@ mapping as JSON, so the user can see the EbId for each of their declared variables? ----- @@ -292,6 +346,14 @@ sql_insert_ebClosure = "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txBytesSize, txBytes) VALUES (?, ?, ?, ?, ?)\n\ \" +sql_share_ebClosures_ASC :: String +sql_share_ebClosures_ASC = + "SELECT txOffset, txHashBytes, txBytes FROM ebTxs\n\ + \WHERE ebId = ? AND txOffset >= ?\n\ + \ORDER BY txOffset ASC\n\ + \LIMIT ?\n\ + \" + ----- withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a @@ -368,6 +430,9 @@ pushX (X n xs vs) x = if n < 1024 then X (n+1) (x : xs) vs else X 1 [x] (V.fromList xs : vs) +revX :: X a -> X a +revX (X n xs vs) = X n (reverse xs) (reverse (map V.reverse vs)) + msgLeiosBlockRequest :: DB.Database -> Int -> IO () msgLeiosBlockRequest db ebId = do -- get the EB items @@ -1258,7 +1323,7 @@ fetchDecision2 db acc0 = do acc2 <- (\f -> foldM f acc1 (Map.toList $ packRequests env dynEnv (MkLeiosRequestDecisions decisions))) $ \acc (peerId, reqs) -> do forM_ reqs $ \req -> do let MkLeiosRequest ebSlot ebHash bitmaps _txHashes = req - putStrLn $ unwords $ "MSG" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps + putStrLn $ unwords $ "MSG MsgLeiosBlockTxsRequest" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps pure $ acc { requestedPerPeer = Map.insertWith (\new old -> old ++ new) peerId reqs (requestedPerPeer acc) } pure acc2 From 1ce37c74ac40950b01626ad4d14b99ef64085ea4 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Wed, 22 Oct 2025 14:19:55 -0700 Subject: [PATCH 043/119] leiosdemo202510: fix off-by-one sterraf noticed --- .../LeiosDemoOnlyTestFetch.hs | 38 ++++++++++--------- 1 file changed, 21 insertions(+), 17 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 2562449f69..484acea684 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -104,11 +104,12 @@ instance Protocol (LeiosFetch point eb tx) where :: ![tx] -> Message (LeiosFetch point eb tx) StBlockTxs StIdle - -- vote request - -- vote reply + -- MsgLeiosVotesRequest + -- MsgLeiosVoteDelivery - -- range request - -- range reply + -- MsgLeiosBlockRangeRequest + -- MsgLeiosNextBlockAndTxsInRange + -- MsgLeiosLastBlockAndTxsInRange MsgDone :: Message (LeiosFetch point eb tx) StIdle StDone @@ -126,10 +127,11 @@ instance NFData (Message (LeiosFetch point eb tx) from to) where MsgLeiosBlock{} -> () MsgLeiosBlockTxsRequest _p bitmaps -> rnf bitmaps MsgLeiosBlockTxs{} -> () - -- vote request - -- vote reply - -- range request - -- range reply + -- MsgLeiosVotesRequest + -- MsgLeiosVoteDelivery + -- MsgLeiosBlockRangeRequest + -- MsgLeiosNextBlockAndTxsInRange + -- MsgLeiosLastBlockAndTxsInRange MsgDone -> () deriving instance (Eq point, Eq eb, Eq tx) @@ -216,10 +218,11 @@ encodeLeiosFetch encodeP encodeEb encodeTx = encode CBOR.encodeListLen 2 <> CBOR.encodeWord 3 <> CBOR.encodeListLenIndef <> foldr (\tx r -> encodeTx tx <> r) CBOR.encodeBreak txs - -- vote request - -- vote reply - -- range request - -- range reply + -- MsgLeiosVotesRequest + -- MsgLeiosVoteDelivery + -- MsgLeiosBlockRangeRequest + -- MsgLeiosNextBlockAndTxsInRange + -- MsgLeiosLastBlockAndTxsInRange MsgDone -> CBOR.encodeListLen 1 <> CBOR.encodeWord 8 @@ -259,11 +262,12 @@ decodeLeiosFetch decodeP decodeEb decodeTx = decode (SingBlockTxs, 2, 3) -> do txs <- CBOR.decodeListLenIndef *> CBOR.decodeSequenceLenIndef (flip (:)) [] reverse decodeTx return $ SomeMessage $ MsgLeiosBlockTxs txs - -- vote request - -- vote reply - -- range request - -- range reply - (SingIdle, 1, 8) -> + -- MsgLeiosVotesRequest + -- MsgLeiosVoteDelivery + -- MsgLeiosBlockRangeRequest + -- MsgLeiosNextBlockAndTxsInRange + -- MsgLeiosLastBlockAndTxsInRange + (SingIdle, 1, 9) -> return $ SomeMessage MsgDone (SingDone, _, _) -> notActiveState stok -- failures per protocol state From dbd74db69ed770187551491932ea68ef89b833ff Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Thu, 23 Oct 2025 11:32:54 +0200 Subject: [PATCH 044/119] Remove unnecessary venvShellHook --- scripts/leios-demo/build.nix | 1 - 1 file changed, 1 deletion(-) diff --git a/scripts/leios-demo/build.nix b/scripts/leios-demo/build.nix index 1e587547bd..de2c1f4ed0 100644 --- a/scripts/leios-demo/build.nix +++ b/scripts/leios-demo/build.nix @@ -20,7 +20,6 @@ widgetsnbextension jupyterlab jupyter - venvShellHook nixpkgs-fmt nil From 25879a4092c6158fa2f3c898c3f7abc056a6d775 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Thu, 23 Oct 2025 15:46:24 +0200 Subject: [PATCH 045/119] Add new options for ImmDB NixOS service --- nix/leios-mvd/immdb-node/service.nix | 16 +++++++++++++++- 1 file changed, 15 insertions(+), 1 deletion(-) diff --git a/nix/leios-mvd/immdb-node/service.nix b/nix/leios-mvd/immdb-node/service.nix index 825a9411ad..b1c8aed659 100644 --- a/nix/leios-mvd/immdb-node/service.nix +++ b/nix/leios-mvd/immdb-node/service.nix @@ -59,6 +59,18 @@ in default = 3001; }; + initialSlot = lib.mkOption { + type = lib.types.int; + description = "Reference slot number (SlotNo). This, together with the initial-time will be used for time translations."; + default = 0; + }; + + initialTime = lib.mkOption { + type = lib.types.nullOr lib.types.int; + description = "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)"; + default = null; + }; + user = lib.mkOption { type = lib.types.str; default = "immdb-server"; @@ -148,7 +160,9 @@ in --db $STATE_DIRECTORY/immutable \ --config $CONFIGURATION_DIRECTORY/config.json \ --address ${cfg.address} \ - --port ${builtins.toString cfg.port}; + --port ${builtins.toString cfg.port} \ + --initial-slot ${builtins.toString cfg.initialSlot} \ + --initial-time ${if cfg.initialTime == null then "$(date +%s)" else builtins.toString cfg.initialTime}; ''; }; From 464dfb0c308af9a4cf4595abfaf4a8cd220409dc Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 11:20:17 -0700 Subject: [PATCH 046/119] leiosdemo202510: some renamings, add MkLeiosBlockRequest ctor --- ouroboros-consensus/app/leiosdemo202510.hs | 51 ++++++++++++---------- 1 file changed, 29 insertions(+), 22 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 6aa5494ccb..eb9d750ce5 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -641,7 +641,7 @@ sql_insert_ebBody = -- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlockTxs msgLeiosBlockTxs :: DB.Database -> LeiosFetchDynamicEnv -> LeiosFetchState -> PeerId -> FilePath -> IO LeiosFetchState msgLeiosBlockTxs db dynEnv lfst0 peerId ebTxsPath = do - (MkLeiosRequest ebSlot ebHash bitmaps0 txHashes, lfst1) <- + (MkLeiosBlockTxsRequest ebSlot ebHash bitmaps0 txHashes, lfst1) <- case Map.lookup peerId (requestedPerPeer lfst0) of Just (req:reqs) -> pure $ (,) req $ lfst0 { requestedPerPeer = @@ -880,7 +880,7 @@ instance JSON.ToJSONKey HashBytes where -- | INVARIANT: no overlap data LeiosFetchState = MkLeiosFetchState { - -- | Which EBs each peer has offered the closure for + -- | Which EBs each peer has offered the closure of -- -- INVARIANT: every set of EBs all exactly agree about the claimed size of each tx -- @@ -888,7 +888,7 @@ data LeiosFetchState = MkLeiosFetchState { offeredEbTxs :: Map PeerId (Set EbId) , -- | Which requests have actually been sent to this peer - requestedPerPeer :: Map PeerId [LeiosRequest] + requestedPerPeer :: Map PeerId [LeiosFetchRequest] , -- | INVARIANT: no empty sets -- @@ -1098,8 +1098,8 @@ sql_scan_missingEbTx = ----- -newtype LeiosRequestDecisions = - MkLeiosRequestDecisions +newtype LeiosFetchDecisions = + MkLeiosFetchDecisions (Map PeerId (Map Word64 (DList (TxHash, TxBytesSize, Map EbId Int)))) deriving (Show) @@ -1110,10 +1110,10 @@ leiosFetchLogicIteration :: -> LeiosFetchState -> - (LeiosFetchState, LeiosRequestDecisions) + (LeiosFetchState, LeiosFetchDecisions) leiosFetchLogicIteration env dynEnv = \acc -> - go1 acc (MkLeiosRequestDecisions Map.empty) + go1 acc (MkLeiosFetchDecisions Map.empty) $ expand $ Map.toDescList $ ebBodies dynEnv @@ -1156,12 +1156,12 @@ leiosFetchLogicIteration env dynEnv = Nothing -> error "impossible!" Just v -> snd $ v IntMap.! txOffset accNew' = - MkLeiosRequestDecisions + MkLeiosFetchDecisions $ Map.insertWith (Map.unionWith (<>)) peerId (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'))) - (let MkLeiosRequestDecisions x = accNew in x) + (let MkLeiosFetchDecisions x = accNew in x) acc' = MkLeiosFetchState { offeredEbTxs = offeredEbTxs acc , @@ -1196,12 +1196,17 @@ leiosFetchLogicIteration env dynEnv = ----- -data LeiosRequest = +data LeiosFetchRequest = + -- | ebSlot, ebHash + MkLeiosBlockRequest + !Word64 + !HashBytes + | -- | ebSlot, ebHash, bitmaps, txHashes -- -- The hashes aren't sent to the peer, but they are used to validate the -- reply when it arrives. - MkLeiosRequest + MkLeiosBlockTxsRequest !Word64 !HashBytes [(Word16, Word64)] @@ -1209,14 +1214,14 @@ data LeiosRequest = deriving (Generic, Show) -- | defaults to @GHC.Generics@ -instance JSON.FromJSON LeiosRequest where {} +instance JSON.FromJSON LeiosFetchRequest where {} -- | defaults to @GHC.Generics@ -instance JSON.ToJSON LeiosRequest where {} +instance JSON.ToJSON LeiosFetchRequest where {} -packRequests :: LeiosFetchStaticEnv -> LeiosFetchDynamicEnv -> LeiosRequestDecisions -> Map PeerId [LeiosRequest] +packRequests :: LeiosFetchStaticEnv -> LeiosFetchDynamicEnv -> LeiosFetchDecisions -> Map PeerId [LeiosFetchRequest] packRequests env dynEnv = - \(MkLeiosRequestDecisions x) -> Map.map goPeer x + \(MkLeiosFetchDecisions x) -> Map.map goPeer x where goPeer = DList.toList @@ -1268,7 +1273,7 @@ packRequests env dynEnv = -> [(Int, (TxHash, TxBytesSize))] -> - DList LeiosRequest + DList LeiosFetchRequest -- TODO the incoming indexes are ascending, so the IntMap accumulator could -- be simplified away goEb ebSlot ebHash !accTxBytesSize !accBitmaps !accN !accHashes = \case @@ -1293,7 +1298,7 @@ packRequests env dynEnv = where flush = - MkLeiosRequest + MkLeiosBlockTxsRequest {- prio -} ebSlot (MkHashBytes ebHash) @@ -1315,15 +1320,17 @@ fetchDecision2 db acc0 = do maxRequestsPerTx = 2 } dynEnv <- loadLeiosFetchDynEnv db - let (acc1, MkLeiosRequestDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 + let (acc1, MkLeiosFetchDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 forM_ (Map.toList decisions) $ \(peerId, slots) -> do forM_ (Map.toDescList slots) $ \(slot, dlist) -> do forM_ dlist $ \(txHash, _txBytesSize, ebIds) -> do putStrLn $ unwords $ "TX" : prettyPeerId peerId : show slot : prettyHashBytes txHash : [ prettyEbId ebId ++ "~" ++ show txOffset | (ebId, txOffset) <- Map.toList ebIds ] - acc2 <- (\f -> foldM f acc1 (Map.toList $ packRequests env dynEnv (MkLeiosRequestDecisions decisions))) $ \acc (peerId, reqs) -> do - forM_ reqs $ \req -> do - let MkLeiosRequest ebSlot ebHash bitmaps _txHashes = req - putStrLn $ unwords $ "MSG MsgLeiosBlockTxsRequest" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps + acc2 <- (\f -> foldM f acc1 (Map.toList $ packRequests env dynEnv (MkLeiosFetchDecisions decisions))) $ \acc (peerId, reqs) -> do + forM_ reqs $ \case + MkLeiosBlockRequest ebSlot ebHash -> do + putStrLn $ unwords ["MSG", "MsgLeiosBlockRequest", prettyPeerId peerId, show ebSlot ,prettyHashBytes ebHash] + MkLeiosBlockTxsRequest ebSlot ebHash bitmaps _txHashes -> do + putStrLn $ unwords $ "MSG" : "MsgLeiosBlockTxsRequest" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps pure $ acc { requestedPerPeer = Map.insertWith (\new old -> old ++ new) peerId reqs (requestedPerPeer acc) } pure acc2 From 88d080da79666fd9fc08f34305e51ef210adf97f Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 13:48:32 -0700 Subject: [PATCH 047/119] leiosdemo202510: some renamings, add EB body requests etc --- ouroboros-consensus/app/leiosdemo202510.hs | 496 +++++++++++++++------ script | 57 +++ 2 files changed, 418 insertions(+), 135 deletions(-) create mode 100755 script diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index eb9d750ce5..9817e93751 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -58,71 +58,94 @@ main = flip asTypeOf main2 $ do main2 :: IO () main2 = getArgs >>= \case - ["generate", dbPath, lfstPath, manifestPath] + ["generate", dbPath, manifestPath] | ".db" `isSuffixOf` dbPath - , ".lfst" `isSuffixOf` lfstPath , ".json" `isSuffixOf` manifestPath -> do doesFileExist dbPath >>= \case True -> die "database path must not exist" False -> pure () - doesFileExist lfstPath >>= \case - True -> die "LeiosFetchState path must not exist" - False -> pure () manifest <- fmap JSON.eitherDecode (BSL.readFile manifestPath) >>= \case Left err -> die err Right x -> pure x db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen generateDb prng0 db manifest - JSON.encodeFile lfstPath emptyLeiosFetchState - ["MsgLeiosBlockRequest", dbPath, ebIdStr] + "ebId-to-point" : dbPath : ebIdStrs | ".db" `isSuffixOf` dbPath - , Just ebId <- readMaybe ebIdStr + , not (null ebIdStrs) + , Just ebIds <- map MkEbId <$> traverse readMaybe ebIdStrs -> do - db <- withDieMsg $ DB.open (fromString dbPath) + dynEnv <- reopenDb dbPath >>= loadLeiosFetchDynEnvHelper False + forM_ ebIds $ \ebId -> do + case ebIdToPoint ebId dynEnv of + Nothing -> die $ "Unknown EbId: " <> prettyEbId ebId + Just (ebSlot, ebHash) -> do + putStrLn $ unwords [show ebSlot, prettyHashBytes (MkHashBytes ebHash)] + ["MsgLeiosBlockOffer", dbPath, lfstPath, peerIdStr, ebSlotStr, ebHashStr, ebBytesSizeStr] + | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath + , not (null peerIdStr) + , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode $ BS8.pack ebHashStr + , Just ebBytesSize <- readMaybe ebBytesSizeStr + -> do + (db, acc) <- openEvenIfMissing dbPath lfstPath + ebId <- ebIdFromPoint' db ebSlot ebHash + acc' <- msgLeiosBlockOffer acc (MkPeerId peerIdStr) ebId ebBytesSize + JSON.encodeFile lfstPath acc' + ["MsgLeiosBlockRequest", dbPath, ebSlotStr, ebHashStr] + | ".db" `isSuffixOf` dbPath + , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode $ BS8.pack ebHashStr + -> do + db <- reopenDb dbPath + ebId <- ebIdFromPoint' db ebSlot ebHash msgLeiosBlockRequest db ebId - ["MsgLeiosBlock", dbPath, ebSlotStr, ebPath] + ["MsgLeiosBlock", dbPath, lfstPath, peerIdStr, ebPath] | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath + , not (null peerIdStr) , ".bin" `isSuffixOf` ebPath + -> do + db <- reopenDb dbPath + acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + acc' <- msgLeiosBlock db acc (MkPeerId peerIdStr) ebPath + JSON.encodeFile lfstPath acc' + ["MsgLeiosBlockTxsOffer", dbPath, lfstPath, peerIdStr, ebSlotStr, ebHashStr] + | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath + , not (null peerIdStr) , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode $ BS8.pack ebHashStr -> do - db <- withDieMsg $ DB.open (fromString dbPath) - msgLeiosBlock db ebSlot ebPath - "MsgLeiosBlockTxsRequest" : dbPath : slotStr : hashStr : bitmapChunkStrs + (db, acc) <- openEvenIfMissing dbPath lfstPath + ebId <- ebIdFromPoint' db ebSlot ebHash + acc' <- msgLeiosBlockTxsOffer acc (MkPeerId peerIdStr) ebId + JSON.encodeFile lfstPath acc' + "MsgLeiosBlockTxsRequest" : dbPath : ebSlotStr : ebHashStr : bitmapChunkStrs | ".db" `isSuffixOf` dbPath - , Just slot <- readMaybe slotStr - , Right hash <- BS16.decode $ BS8.pack hashStr + , Just ebSlot <- readMaybe ebSlotStr + , Right ebHash <- BS16.decode $ BS8.pack ebHashStr , Just bitmaps <- parseBitmaps bitmapChunkStrs -> do - db <- withDieMsg $ DB.open (fromString dbPath) - dynEnv <- loadLeiosFetchDynEnvHelper False db - let ebId = fst $ ebIdFromPoint slot hash dynEnv + db <- reopenDb dbPath + ebId <- ebIdFromPoint' db ebSlot ebHash msgLeiosBlockTxsRequest db ebId bitmaps ["MsgLeiosBlockTxs", dbPath, lfstPath, peerIdStr, ebTxsPath] | ".db" `isSuffixOf` dbPath , ".bin" `isSuffixOf` ebTxsPath , not (null peerIdStr) -> do - db <- withDieMsg $ DB.open (fromString dbPath) - dynEnv <- loadLeiosFetchDynEnvHelper False db - acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath - acc' <- msgLeiosBlockTxs db dynEnv acc (MkPeerId peerIdStr) ebTxsPath - JSON.encodeFile lfstPath acc' - "MsgLeiosBlockTxsOffer" : lfstPath : peerIdStr : ebIdStrs - | ".lfst" `isSuffixOf` lfstPath - , not (null peerIdStr) - , Just ebIds <- map MkEbId <$> traverse readMaybe ebIdStrs - , not (null ebIds) - -> do + db <- reopenDb dbPath acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath - acc' <- msgLeiosBlockTxsOffer acc (MkPeerId peerIdStr) ebIds + acc' <- msgLeiosBlockTxs db acc (MkPeerId peerIdStr) ebTxsPath JSON.encodeFile lfstPath acc' ["fetch-logic-iteration", dbPath, lfstPath] | ".db" `isSuffixOf` dbPath , ".lfst" `isSuffixOf` lfstPath -> do - db <- withDieMsg $ DB.open (fromString dbPath) + db <- reopenDb dbPath acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath acc' <- fetchDecision2 db acc JSON.encodeFile lfstPath acc' @@ -130,15 +153,24 @@ main2 = getArgs >>= \case | ".bin" `isSuffixOf` ebTxsPath -> do hashTxs ebTxsPath - _ -> die "Either $0 generate my.db myManifest.json\n\ - \ OR $0 MsgLeiosBlockRequest my.db ebId\n\ - \ OR $0 MsgLeiosBlock my.db ebId myEb.bin\n\ - \ OR $0 MsgLeiosBlockTxsRequest my.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ - \ OR $0 MsgLeiosBlockTxs my.db my.lfst peerId myEbTxs.bin\n\ - \ OR $0 fetch-logic-iteration my.db my.lfst\n\ - \ OR $0 hash-txs myEbTxs.bin\n\ - \ OR $0 MsgLeiosBlockTxsOffer my.lfst peerId ebId ebId ebId ...\n\ - \" + _ -> + die "Either $0 generate my.db myManifest.json\n\ + \ OR $0 ebId-to-point my.db ebId ebId ebId...\n\ + \ OR $0 MsgLeiosBlockOffer my.db my.lfst peerId ebSlot ebHash(hex) ebBytesSize\n\ + \ OR $0 MsgLeiosBlockRequest my.db ebSlot ebHash(hex)\n\ + \ OR $0 MsgLeiosBlock my.db my.lfst myEb.bin\n\ + \ OR $0 MsgLeiosBlockTxsOffer my.db my.lfst peerId ebSlot ebHash(hex)\n\ + \ OR $0 MsgLeiosBlockTxsRequest my.db ebSlot ebHash(hex) index16:bitmap64 index16:bitmap64 index16:bitmap64 ...\n\ + \ OR $0 MsgLeiosBlockTxs my.db my.lfst peerId myEbTxs.bin\n\ + \ OR $0 fetch-logic-iteration my.db my.lfst\n\ + \ OR $0 hash-txs myEbTxs.bin\n\ + \" + +reopenDb :: FilePath -> IO DB.Database +reopenDb dbPath = do + doesFileExist dbPath >>= \case + True -> withDieMsg $ DB.open (fromString dbPath) + False -> die $ "No such file: " ++ dbPath parseBitmaps :: [String] -> Maybe [(Word16, Word64)] parseBitmaps = @@ -257,9 +289,9 @@ generateDb prng0 db ebRecipes = do $ Hash.hashWithSerialiser (encodeEB (fromIntegral . BS.length) (\(MkHashBytes x) -> x)) txs - let (ebId, dynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv + let (ebId, mbDynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv withDieMsg $ DB.exec db (fromString "BEGIN") - withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegralEbId ebId) + withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegralEbId ebId) withDie $ DB.bindInt64 stmt_write_ebClosure 1 (fromIntegralEbId ebId) -- INSERT INTO ebPoints withDie $ DB.bindInt64 stmt_write_ebId 1 (fromIntegral ebSlot) @@ -277,7 +309,7 @@ generateDb prng0 db ebRecipes = do withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") - pure (dynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeBinder ebRecipe) sigma) + pure (fromMaybe dynEnv mbDynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeBinder ebRecipe) sigma) -- finalize db withDieMsg $ DB.exec db (fromString sql_index_schema) -- TODO maybe print out the @sigma@ mapping as JSON, so the user can see the EbId for each of their declared variables? @@ -297,11 +329,11 @@ sql_schema = \CREATE TABLE ebPoints (\n\ \ ebSlot INTEGER NOT NULL\n\ \ ,\n\ - \ ebHash BLOB NOT NULL\n\ + \ ebHashBytes BLOB NOT NULL\n\ \ ,\n\ \ ebId INTEGER NOT NULL\n\ \ ,\n\ - \ PRIMARY KEY (ebSlot, ebHash)\n\ + \ PRIMARY KEY (ebSlot, ebHashBytes)\n\ \ ) WITHOUT ROWID;\n\ \\n\ \CREATE TABLE ebTxs (\n\ @@ -338,7 +370,7 @@ sql_index_schema = sql_insert_ebId :: String sql_insert_ebId = - "INSERT INTO ebPoints (ebSlot, ebHash, ebId) VALUES (?, ?, ?)\n\ + "INSERT INTO ebPoints (ebSlot, ebHashBytes, ebId) VALUES (?, ?, ?)\n\ \" sql_insert_ebClosure :: String @@ -433,11 +465,11 @@ pushX (X n xs vs) x = revX :: X a -> X a revX (X n xs vs) = X n (reverse xs) (reverse (map V.reverse vs)) -msgLeiosBlockRequest :: DB.Database -> Int -> IO () +msgLeiosBlockRequest :: DB.Database -> EbId -> IO () msgLeiosBlockRequest db ebId = do -- get the EB items stmt <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) - withDie $ DB.bindInt64 stmt 1 (fromIntegral ebId) + withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) let loop !acc = withDie (DB.stepNoCB stmt) >>= \case DB.Done -> pure acc @@ -517,10 +549,10 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do $ CBOR.encodeListLenIndef <> foldr (\bs r -> CBOR.encodePreEncoded bs <> r) CBOR.encodeBreak acc putStrLn "" -maxEbBodyBytesSize :: Int +maxEbBodyBytesSize :: BytesSize maxEbBodyBytesSize = 500000 -minEbItemBytesSize :: Int +minEbItemBytesSize :: BytesSize minEbItemBytesSize = (1 + 32 + 1) + (1 + 1) maxEbItems :: Int @@ -592,23 +624,26 @@ sql_lookup_ebClosures_DESC n = -- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlock -- -- PREREQ: No row in ebTxs already has this ebId. -msgLeiosBlock :: DB.Database -> Word64 -> FilePath -> IO () -msgLeiosBlock db ebSlot ebPath = do +msgLeiosBlock :: DB.Database -> LeiosFetchState -> PeerId -> FilePath -> IO LeiosFetchState +msgLeiosBlock db lfst0 peerId ebPath = do + (MkLeiosBlockRequest ebSlot ebHash, lfst1) <- + case Map.lookup peerId (requestedPerPeer lfst0) of + Just (LeiosBlockRequest req:reqs) -> pure $ (,) req $ lfst0 { + requestedPerPeer = + if null reqs then Map.delete peerId (requestedPerPeer lfst0) else + Map.insert peerId reqs (requestedPerPeer lfst0) + } + _ -> die "Not expecting MsgLeiosBlock" ebBytes <- BS.readFile ebPath - let ebHash :: Hash.Hash HASH ByteString - ebHash = Hash.castHash $ Hash.hashWith id ebBytes - ebId <- do - dynEnv <- loadLeiosFetchDynEnvHelper False db - pure $ fst $ ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv - stmt_write_ebIds <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) + let ebBytesSize = BS.length ebBytes + let ebHash' :: Hash.Hash HASH ByteString + ebHash' = Hash.castHash $ Hash.hashWith id ebBytes + ebHash'' = MkHashBytes $ Hash.hashToBytes ebHash' + when (ebHash /= ebHash'') $ do + die $ "MsgLeiosBlock hash mismatch: " <> show (ebHash, ebHash'') + ebId <- ebIdFromPoint' db ebSlot (let MkHashBytes x = ebHash in x) stmt_write_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) withDieMsg $ DB.exec db (fromString "BEGIN") - -- INSERT INTO ebPoints - withDie $ DB.bindInt64 stmt_write_ebIds 1 (fromIntegral ebSlot) - withDie $ DB.bindBlob stmt_write_ebIds 2 (Hash.hashToBytes ebHash) - withDie $ DB.bindInt64 stmt_write_ebIds 3 (fromIntegralEbId ebId) - withDieDone $ DB.stepNoCB stmt_write_ebIds - withDie $ DB.reset stmt_write_ebIds -- decode incrementally and simultaneously INSERT INTO ebTxs withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegralEbId ebId) let decodeBreakOrEbPair = do @@ -632,6 +667,25 @@ msgLeiosBlock db ebSlot ebPath = do go1 0 ebBytes2 -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") + pure lfst1 { + acquiredEbBodies = Set.insert ebId (acquiredEbBodies lfst1) + , + missingEbBodies = Map.delete ebId (missingEbBodies lfst1) + , + requestedBytesSize = requestedBytesSize lfst1 - ebBytesSize + , + requestedBytesSizePerPeer = + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIfZero $ x - ebBytesSize + ) + peerId + (requestedBytesSizePerPeer lfst1) + , + requestedEbPeers = + Map.update (delIfNull . Set.delete peerId) ebId (requestedEbPeers lfst1) + } sql_insert_ebBody :: String sql_insert_ebBody = @@ -639,17 +693,17 @@ sql_insert_ebBody = \" -- | PREREQ: the file is the CBOR encoding (binary, not hex) of the payload of a MsgLeiosBlockTxs -msgLeiosBlockTxs :: DB.Database -> LeiosFetchDynamicEnv -> LeiosFetchState -> PeerId -> FilePath -> IO LeiosFetchState -msgLeiosBlockTxs db dynEnv lfst0 peerId ebTxsPath = do +msgLeiosBlockTxs :: DB.Database -> LeiosFetchState -> PeerId -> FilePath -> IO LeiosFetchState +msgLeiosBlockTxs db lfst0 peerId ebTxsPath = do (MkLeiosBlockTxsRequest ebSlot ebHash bitmaps0 txHashes, lfst1) <- case Map.lookup peerId (requestedPerPeer lfst0) of - Just (req:reqs) -> pure $ (,) req $ lfst0 { + Just (LeiosBlockTxsRequest req:reqs) -> pure $ (,) req $ lfst0 { requestedPerPeer = if null reqs then Map.delete peerId (requestedPerPeer lfst0) else Map.insert peerId reqs (requestedPerPeer lfst0) } - _ -> die "No such outstanding request" - let ebId = fst $ ebIdFromPoint ebSlot (let MkHashBytes x = ebHash in x) dynEnv + _ -> die "Not expecting MsgLeiosBlockTxs" + ebId <- ebIdFromPoint' db ebSlot (let MkHashBytes x = ebHash in x) ebTxsBytes <- BSL.readFile ebTxsPath stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) withDie $ DB.bindInt64 stmt 2 (fromIntegralEbId ebId) @@ -686,7 +740,6 @@ msgLeiosBlockTxs db dynEnv lfst0 peerId ebTxsPath = do withDie $ DB.bindBlob stmt 1 $ serialize' $ CBOR.encodeBytes txBytes withDieDone $ DB.stepNoCB stmt withDie $ DB.reset stmt - let delIfNull x = if Set.null x then Nothing else Just x go1 (Map.update (delIfNull . Set.delete peerId) txHash accRequested) (accTxBytesSize + txBytesSize) @@ -709,18 +762,16 @@ msgLeiosBlockTxs db dynEnv lfst0 peerId ebTxsPath = do -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") pure lfst1 { - requestedTxBytesSize = requestedTxBytesSize lfst1 - txBytesSize + requestedBytesSize = requestedBytesSize lfst1 - txBytesSize , - requestedTxBytesSizePerPeer = - let delIfZero x = if 0 == x then Nothing else Just x - in + requestedBytesSizePerPeer = Map.alter (\case Nothing -> error "impossible!" Just x -> delIfZero $ x - txBytesSize ) peerId - (requestedTxBytesSizePerPeer lfst1) + (requestedBytesSizePerPeer lfst1) , requestedTxPeers = requested' } @@ -741,7 +792,7 @@ _maxTxOffsetBitWidth = ceiling $ log (fromIntegral maxEbItems :: Double) / log 2 maxRequestsPerIteration :: Int maxRequestsPerIteration = 10 -maxBytesSizePerRequest :: Int +maxBytesSizePerRequest :: BytesSize maxBytesSizePerRequest = 500000 fetchDecision :: DB.Database -> IntSet.IntSet -> IO () @@ -880,32 +931,44 @@ instance JSON.ToJSONKey HashBytes where -- | INVARIANT: no overlap data LeiosFetchState = MkLeiosFetchState { + -- | Which EBs each peer has offered the body of + -- + -- TODO reverse index for when EBs age out? + offeredEbs :: Map PeerId (Set EbId) + , -- | Which EBs each peer has offered the closure of -- -- INVARIANT: every set of EBs all exactly agree about the claimed size of each tx -- -- TODO reverse index for when EBs age out? offeredEbTxs :: Map PeerId (Set EbId) + , + -- | EBs whose bodies have been received + acquiredEbBodies :: Set EbId + , + -- | EBs whose bodies have been offered but never received + missingEbBodies :: Map EbId BytesSize , -- | Which requests have actually been sent to this peer requestedPerPeer :: Map PeerId [LeiosFetchRequest] , -- | INVARIANT: no empty sets - -- - -- INVARIANT: @<= maxRequestedTxBytes@ + requestedEbPeers :: Map EbId (Set PeerId) + , + -- | INVARIANT: no empty sets -- -- TODO may need to also store priority here requestedTxPeers :: Map TxHash (Set PeerId) , - -- | Outstanding requested 'TxBytesSize' for each peer + -- | Outstanding requested bytes for each peer -- - -- INVARIANT: @Map.all (<= maxRequestedTxBytesPerPeer)@ - requestedTxBytesSizePerPeer :: Map PeerId TxBytesSize + -- INVARIANT: @Map.all (<= maxRequestedBytesSizePerPeer)@ + requestedBytesSizePerPeer :: Map PeerId BytesSize , - -- | Sum of 'requestedTxBytesSizePerPeer' + -- | Sum of 'requestedBytesSizePerPeer' -- - -- INVARIANT: @<= maxRequestedTxBytes@ - requestedTxBytesSize :: TxBytesSize + -- INVARIANT: @<= maxRequestedBytesSize@ + requestedBytesSize :: BytesSize } deriving (Generic) @@ -918,6 +981,10 @@ instance JSON.ToJSON LeiosFetchState where {} emptyLeiosFetchState :: LeiosFetchState emptyLeiosFetchState = MkLeiosFetchState + Map.empty + Map.empty + Set.empty + Map.empty Map.empty Map.empty Map.empty @@ -934,40 +1001,59 @@ ebIdToPoint (MkEbId y) x = where f (MkHashBytes z) = (ebIdSlot (MkEbId y), z) -ebIdFromPoint :: Word64 -> ByteString -> LeiosFetchDynamicEnv -> (EbId, LeiosFetchDynamicEnv) -ebIdFromPoint slotNo hash x = - case IntMap.lookup (fromIntegral slotNo) (ebPoints x) of +ebIdFromPoint :: Word64 -> ByteString -> LeiosFetchDynamicEnv -> (EbId, Maybe LeiosFetchDynamicEnv) +ebIdFromPoint ebSlot ebHash x = + case IntMap.lookup (fromIntegral ebSlot) (ebPoints x) of Just m -> case Map.lookup hashBytes m of - Just y -> (y, x) + Just y -> (y, Nothing) Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) - Map.size m Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) where - hashBytes = MkHashBytes hash + hashBytes = MkHashBytes ebHash - zero = fromIntegral ((slotNo `Bits.unsafeShiftL` 20) :: Word64) + minBound :: Int + zero = fromIntegral ((ebSlot `Bits.unsafeShiftL` 20) :: Word64) + minBound :: Int gen y = (,) y - $ x { ebPoints = IntMap.insertWith Map.union (fromIntegral slotNo) (Map.singleton hashBytes y) (ebPoints x) + $ Just + $ x { ebPoints = IntMap.insertWith Map.union (fromIntegral ebSlot) (Map.singleton hashBytes y) (ebPoints x) , ebPointsInverse = let MkEbId z = y in IntMap.insert z hashBytes (ebPointsInverse x) } +ebIdFromPoint' :: DB.Database -> Word64 -> ByteString -> IO EbId +ebIdFromPoint' db ebSlot ebHash = do + dynEnv <- loadLeiosFetchDynEnvHelper False db + let (ebId, mbDynEnv') = ebIdFromPoint ebSlot ebHash dynEnv + case mbDynEnv' of + Nothing -> pure () + Just{} -> do + -- INSERT INTO ebPoints + stmt_write_ebIds <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) + withDie $ DB.bindInt64 stmt_write_ebIds 1 (fromIntegral ebSlot) + withDie $ DB.bindBlob stmt_write_ebIds 2 ebHash + withDie $ DB.bindInt64 stmt_write_ebIds 3 (fromIntegralEbId ebId) + withDieDone $ DB.stepNoCB stmt_write_ebIds + pure ebId + ----- -type TxBytesSize = Int +type BytesSize = Int type TxHash = HashBytes data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { -- | At most this many outstanding bytes requested from all peers together - maxRequestedTxBytes :: TxBytesSize + maxRequestedBytesSize :: Int , -- | At most this many outstanding bytes requested from each peer - maxRequestedTxBytesPerPeer :: TxBytesSize + maxRequestedBytesSizePerPeer :: Int , -- | At most this many outstanding bytes per request - maxRequestTxBytesSize :: TxBytesSize + maxRequestBytesSize :: Int + , + -- | At most this many outstanding requests for each EB body + maxRequestsPerEb :: Int , -- | At most this many outstanding requests for each individual tx maxRequestsPerTx :: Int @@ -1018,7 +1104,7 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv missingTxBodies :: Set TxHash , -- | All missing txs in the context of EBs worth retrieving the closure for - ebBodies :: Map EbId (IntMap (TxHash, TxBytesSize)) + ebBodies :: Map EbId (IntMap (TxHash, BytesSize)) , -- | Reverse index of 'ebBodies' -- @@ -1083,7 +1169,7 @@ loadLeiosFetchDynEnvHelper full db = do sql_scan_ebId :: String sql_scan_ebId = - "SELECT ebSlot, ebHash, ebId\n\ + "SELECT ebSlot, ebHashBytes, ebId\n\ \FROM ebPoints\n\ \ORDER BY ebId ASC\n\ \" @@ -1100,7 +1186,7 @@ sql_scan_missingEbTx = newtype LeiosFetchDecisions = MkLeiosFetchDecisions - (Map PeerId (Map Word64 (DList (TxHash, TxBytesSize, Map EbId Int)))) + (Map PeerId (Map Word64 (DList (TxHash, BytesSize, Map EbId Int), DList EbId))) deriving (Show) leiosFetchLogicIteration :: @@ -1116,39 +1202,98 @@ leiosFetchLogicIteration env dynEnv = go1 acc (MkLeiosFetchDecisions Map.empty) $ expand $ Map.toDescList - $ ebBodies dynEnv + $ Map.map Left (missingEbBodies acc) `Map.union` Map.map Right (ebBodies dynEnv) where expand = \case [] -> [] - (ebId, v):vs -> - [ (ebId, txHash) | (txHash, _txBytesSize) <- IntMap.elems v ] + (ebId, Left ebByteSize):vs -> Left (ebId, ebByteSize) : expand vs + (ebId, Right v):vs -> + [ Right (ebId, txHash) | (txHash, _txBytesSize) <- IntMap.elems v ] <> expand vs go1 !acc !accNew = \case [] -> (acc, accNew) - (ebId, txHash):txHashes + Left (ebId, ebBytesSize) : targets + | let peerIds :: Set PeerId + peerIds = Map.findWithDefault Set.empty ebId (requestedEbPeers acc) + -> goEb2 acc accNew targets ebId ebBytesSize peerIds + + Right (ebId, txHash) : targets | Set.member txHash (missingTxBodies dynEnv) -- we don't already have it , let !txOffsets = case Map.lookup txHash (txOffsetss dynEnv) of Nothing -> error "impossible!" Just x -> x , let peerIds :: Set PeerId - !peerIds = Map.findWithDefault Set.empty txHash (requestedTxPeers acc) - -> go2 acc accNew txHashes (ebIdSlot ebId) txHash txOffsets peerIds + peerIds = Map.findWithDefault Set.empty txHash (requestedTxPeers acc) + -> goTx2 acc accNew targets (ebIdSlot ebId) txHash txOffsets peerIds | otherwise - -> go1 acc accNew txHashes + -> go1 acc accNew targets + + goEb2 !acc !accNew targets ebId ebBytesSize peerIds + | requestedBytesSize acc >= maxRequestedBytesSize env -- we can't request anything + = (acc, accNew) + + | Set.size peerIds < maxRequestsPerEb env -- we would like to request it from an additional peer + , Just peerId <- choosePeerEb peerIds acc ebId + -- there's a peer who offered it and we haven't already requested it from them + = let accNew' = + MkLeiosFetchDecisions + $ Map.insertWith + (Map.unionWith (<>)) + peerId + (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton ebId)) + (let MkLeiosFetchDecisions x = accNew in x) + acc' = MkLeiosFetchState { + offeredEbs = offeredEbs acc + , + offeredEbTxs = offeredEbTxs acc + , + acquiredEbBodies = acquiredEbBodies acc + , + missingEbBodies = missingEbBodies acc + , + requestedPerPeer = requestedPerPeer acc + , + requestedEbPeers = Map.insertWith Set.union ebId (Set.singleton peerId) (requestedEbPeers acc) + , + requestedTxPeers = requestedTxPeers acc + , + requestedBytesSizePerPeer = Map.insertWith (+) peerId ebBytesSize (requestedBytesSizePerPeer acc) + , + requestedBytesSize = ebBytesSize + requestedBytesSize acc + } + peerIds' = Set.insert peerId peerIds + in + goEb2 acc' accNew' targets ebId ebBytesSize peerIds' + + | otherwise + = go1 acc accNew targets + + choosePeerEb :: Set PeerId -> LeiosFetchState -> EbId -> Maybe PeerId + choosePeerEb peerIds acc ebId = + foldr (\a _ -> Just a) Nothing + $ [ peerId + | (peerId, ebIds) <- + Map.toList -- TODO prioritize/shuffle? + $ (`Map.withoutKeys` peerIds) -- not already requested from this peer + $ offeredEbs acc + , Map.findWithDefault 0 peerId (requestedBytesSizePerPeer acc) <= maxRequestedBytesSizePerPeer env + -- peer can be sent more requests + , ebId `Set.member` ebIds -- peer has offered this EB body + ] - go2 !acc !accNew txHashes ebSlot txHash txOffsets peerIds + goTx2 !acc !accNew targets ebSlot txHash txOffsets peerIds - | requestedTxBytesSize acc >= maxRequestedTxBytes env -- we can't request anything + | requestedBytesSize acc >= maxRequestedBytesSize env -- we can't request anything = (acc, accNew) | Set.size peerIds < maxRequestsPerTx env -- we would like to request it from an additional peer -- TODO if requests list priority, does this limit apply even if the -- tx has only been requested at lower priorities? - , Just (peerId, txOffsets') <- choosePeer peerIds acc txOffsets + , Just (peerId, txOffsets') <- choosePeerTx peerIds acc txOffsets -- there's a peer who offered it and we haven't already requested it from them = let txBytesSize = case Map.lookupMax txOffsets' of Nothing -> error "impossible!" @@ -1160,35 +1305,43 @@ leiosFetchLogicIteration env dynEnv = $ Map.insertWith (Map.unionWith (<>)) peerId - (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'))) + (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'), DList.empty)) (let MkLeiosFetchDecisions x = accNew in x) acc' = MkLeiosFetchState { + offeredEbs = offeredEbs acc + , offeredEbTxs = offeredEbTxs acc + , + acquiredEbBodies = acquiredEbBodies acc + , + missingEbBodies = missingEbBodies acc , requestedPerPeer = requestedPerPeer acc + , + requestedEbPeers = requestedEbPeers acc , requestedTxPeers = Map.insertWith Set.union txHash (Set.singleton peerId) (requestedTxPeers acc) , - requestedTxBytesSizePerPeer = Map.insertWith (+) peerId txBytesSize (requestedTxBytesSizePerPeer acc) + requestedBytesSizePerPeer = Map.insertWith (+) peerId txBytesSize (requestedBytesSizePerPeer acc) , - requestedTxBytesSize = txBytesSize + requestedTxBytesSize acc + requestedBytesSize = txBytesSize + requestedBytesSize acc } peerIds' = Set.insert peerId peerIds in - go2 acc' accNew' txHashes ebSlot txHash txOffsets peerIds' + goTx2 acc' accNew' targets ebSlot txHash txOffsets peerIds' | otherwise - = go1 acc accNew txHashes + = go1 acc accNew targets - choosePeer :: Set PeerId -> LeiosFetchState -> Map EbId Int -> Maybe (PeerId, Map EbId Int) - choosePeer peerIds acc txOffsets = + choosePeerTx :: Set PeerId -> LeiosFetchState -> Map EbId Int -> Maybe (PeerId, Map EbId Int) + choosePeerTx peerIds acc txOffsets = foldr (\a _ -> Just a) Nothing $ [ (peerId, txOffsets') | (peerId, ebIds) <- Map.toList -- TODO prioritize/shuffle? $ (`Map.withoutKeys` peerIds) -- not already requested from this peer $ offeredEbTxs acc - , Map.findWithDefault 0 peerId (requestedTxBytesSizePerPeer acc) <= maxRequestedTxBytesPerPeer env + , Map.findWithDefault 0 peerId (requestedBytesSizePerPeer acc) <= maxRequestedBytesSizePerPeer env -- peer can be sent more requests , let txOffsets' = txOffsets `Map.restrictKeys` ebIds , not $ Map.null txOffsets' -- peer has offered an EB closure that includes this tx @@ -1197,11 +1350,31 @@ leiosFetchLogicIteration env dynEnv = ----- data LeiosFetchRequest = + LeiosBlockRequest LeiosBlockRequest + | + LeiosBlockTxsRequest LeiosBlockTxsRequest + deriving (Generic, Show) + +-- | defaults to @GHC.Generics@ +instance JSON.FromJSON LeiosFetchRequest where {} + +-- | defaults to @GHC.Generics@ +instance JSON.ToJSON LeiosFetchRequest where {} + +data LeiosBlockRequest = -- | ebSlot, ebHash MkLeiosBlockRequest !Word64 !HashBytes - | + deriving (Generic, Show) + +-- | defaults to @GHC.Generics@ +instance JSON.FromJSON LeiosBlockRequest where {} + +-- | defaults to @GHC.Generics@ +instance JSON.ToJSON LeiosBlockRequest where {} + +data LeiosBlockTxsRequest = -- | ebSlot, ebHash, bitmaps, txHashes -- -- The hashes aren't sent to the peer, but they are used to validate the @@ -1214,10 +1387,10 @@ data LeiosFetchRequest = deriving (Generic, Show) -- | defaults to @GHC.Generics@ -instance JSON.FromJSON LeiosFetchRequest where {} +instance JSON.FromJSON LeiosBlockTxsRequest where {} -- | defaults to @GHC.Generics@ -instance JSON.ToJSON LeiosFetchRequest where {} +instance JSON.ToJSON LeiosBlockTxsRequest where {} packRequests :: LeiosFetchStaticEnv -> LeiosFetchDynamicEnv -> LeiosFetchDecisions -> Map PeerId [LeiosFetchRequest] packRequests env dynEnv = @@ -1226,10 +1399,19 @@ packRequests env dynEnv = goPeer = DList.toList . Map.foldlWithKey - (\acc prio txs -> goPrio prio txs <> acc) + (\acc prio (txs, ebs) -> goPrioTx prio txs <> goPrioEb prio ebs <> acc) + -- TODO priority within same slot? DList.empty - goPrio _prio txs = + goPrioEb _prio ebs = + DList.map + (\ebId -> case ebIdToPoint ebId dynEnv of + Nothing -> error "impossible!" + Just (ebSlot, ebHash) -> LeiosBlockRequest $ MkLeiosBlockRequest ebSlot (MkHashBytes ebHash) + ) + ebs + + goPrioTx _prio txs = Map.foldlWithKey (\acc ebId txs' -> case ebIdToPoint ebId dynEnv of @@ -1263,7 +1445,7 @@ packRequests env dynEnv = -> ByteString -> - TxBytesSize + BytesSize -> IntMap Word64 -> @@ -1271,7 +1453,7 @@ packRequests env dynEnv = -> DList TxHash -> - [(Int, (TxHash, TxBytesSize))] + [(Int, (TxHash, BytesSize))] -> DList LeiosFetchRequest -- TODO the incoming indexes are ascending, so the IntMap accumulator could @@ -1280,7 +1462,7 @@ packRequests env dynEnv = [] -> if 0 < accN then DList.singleton flush else DList.empty (txOffset, (txHash, txBytesSize)):txs - | maxRequestTxBytesSize env < accTxBytesSize' + | maxRequestBytesSize env < accTxBytesSize' -> flush `DList.cons` goEb ebSlot ebHash 0 IntMap.empty 0 DList.empty txs | otherwise @@ -1298,7 +1480,8 @@ packRequests env dynEnv = where flush = - MkLeiosBlockTxsRequest + LeiosBlockTxsRequest + $ MkLeiosBlockTxsRequest {- prio -} ebSlot (MkHashBytes ebHash) @@ -1311,33 +1494,76 @@ fetchDecision2 :: DB.Database -> LeiosFetchState -> IO LeiosFetchState fetchDecision2 db acc0 = do let env = MkLeiosFetchStaticEnv { - maxRequestedTxBytes = 50 * 10^(6 :: Int) + maxRequestedBytesSize = 50 * 10^(6 :: Int) , - maxRequestedTxBytesPerPeer = 5 * 10^(6 :: Int) + maxRequestedBytesSizePerPeer = 5 * 10^(6 :: Int) , - maxRequestTxBytesSize = 500000 + maxRequestBytesSize = 500000 + , + maxRequestsPerEb = 2 , maxRequestsPerTx = 2 } dynEnv <- loadLeiosFetchDynEnv db let (acc1, MkLeiosFetchDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 forM_ (Map.toList decisions) $ \(peerId, slots) -> do - forM_ (Map.toDescList slots) $ \(slot, dlist) -> do - forM_ dlist $ \(txHash, _txBytesSize, ebIds) -> do + forM_ (Map.toDescList slots) $ \(slot, (_txs, ebs)) -> do + forM_ ebs $ \ebId -> do + putStrLn $ unwords ["EB", prettyPeerId peerId, show slot, prettyEbId ebId] + forM_ (Map.toDescList slots) $ \(slot, (txs, _ebs)) -> do + forM_ txs $ \(txHash, _txBytesSize, ebIds) -> do putStrLn $ unwords $ "TX" : prettyPeerId peerId : show slot : prettyHashBytes txHash : [ prettyEbId ebId ++ "~" ++ show txOffset | (ebId, txOffset) <- Map.toList ebIds ] acc2 <- (\f -> foldM f acc1 (Map.toList $ packRequests env dynEnv (MkLeiosFetchDecisions decisions))) $ \acc (peerId, reqs) -> do forM_ reqs $ \case - MkLeiosBlockRequest ebSlot ebHash -> do + LeiosBlockRequest (MkLeiosBlockRequest ebSlot ebHash) -> do putStrLn $ unwords ["MSG", "MsgLeiosBlockRequest", prettyPeerId peerId, show ebSlot ,prettyHashBytes ebHash] - MkLeiosBlockTxsRequest ebSlot ebHash bitmaps _txHashes -> do + LeiosBlockTxsRequest (MkLeiosBlockTxsRequest ebSlot ebHash bitmaps _txHashes) -> do putStrLn $ unwords $ "MSG" : "MsgLeiosBlockTxsRequest" : prettyPeerId peerId : show ebSlot : prettyHashBytes ebHash : map prettyBitmap bitmaps pure $ acc { requestedPerPeer = Map.insertWith (\new old -> old ++ new) peerId reqs (requestedPerPeer acc) } pure acc2 ----- -msgLeiosBlockTxsOffer :: LeiosFetchState -> PeerId -> [EbId] -> IO LeiosFetchState -msgLeiosBlockTxsOffer acc peerId ebIds = do +openEvenIfMissing :: FilePath -> FilePath -> IO (DB.Database, LeiosFetchState) +openEvenIfMissing dbPath lfstPath = do + db <- do + b <- doesFileExist dbPath + db <- withDieMsg $ DB.open (fromString dbPath) + when (not b) $ do + withDieMsg $ DB.exec db (fromString sql_schema) + withDieMsg $ DB.exec db (fromString sql_index_schema) + pure db + lfst <- doesFileExist lfstPath >>= \case + True -> withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + False -> do + JSON.encodeFile lfstPath emptyLeiosFetchState + pure emptyLeiosFetchState + pure (db, lfst) + +msgLeiosBlockOffer :: LeiosFetchState -> PeerId -> EbId -> BytesSize -> IO LeiosFetchState +msgLeiosBlockOffer acc peerId ebId ebBytesSize = do + pure acc { + offeredEbs = Map.insertWith Set.union peerId (Set.singleton ebId) (offeredEbs acc) + , + missingEbBodies = + ( if Set.member ebId (acquiredEbBodies acc) then id else + Map.insert ebId ebBytesSize + ) + $ missingEbBodies acc + } + +msgLeiosBlockTxsOffer :: LeiosFetchState -> PeerId -> EbId -> IO LeiosFetchState +msgLeiosBlockTxsOffer acc peerId ebId = do pure acc { - offeredEbTxs = Map.insertWith Set.union peerId (Set.fromList ebIds) (offeredEbTxs acc) + offeredEbs = Map.insertWith Set.union peerId (Set.singleton ebId) (offeredEbs acc) + , + offeredEbTxs = Map.insertWith Set.union peerId (Set.singleton ebId) (offeredEbTxs acc) } + +----- + +delIfNull :: Set a -> Maybe (Set a) +delIfNull x = if Set.null x then Nothing else Just x + +delIfZero :: (Eq a, Num a) => a -> Maybe a +delIfZero x = if 0 == x then Nothing else Just x diff --git a/script b/script new file mode 100755 index 0000000000..861efac37e --- /dev/null +++ b/script @@ -0,0 +1,57 @@ +#! /bin/bash +rm -f tmp/my.db tmp/up.db tmp/my.lfst tmp/demo tmp/reqBlocks tmp/reqBlockTxss +set -eux +cabal build exe:leiosdemo202510 +ln -s $(cabal list-bin exe:leiosdemo202510) tmp/demo +tmp/demo generate tmp/up.db tmp/myManifest.json +# MsgLeiosBlock messages +sqlite3 tmp/up.db "SELECT ebSlot, PRINTF('%X', ebId), ebId FROM ebPoints ORDER BY ebId ASC" # dump points +sqlite3 tmp/up.db "SELECT PRINTF('%d %s', ebSlot, HEX(ebHashBytes)) FROM ebPoints ORDER BY ebId DESC" | while IFS= read -r line; do + tmp/demo MsgLeiosBlockRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + sz=$(stat -c %s tmp/foo.bin) + tmp/demo MsgLeiosBlockOffer tmp/my.db tmp/my.lfst Alice $line $sz +done +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +cat tmp/reqs | grep -e MsgLeiosBlockRequest | grep -e Alice | cut -d' ' -f4- | while IFS= read -r line; do + set -x + tmp/demo MsgLeiosBlockRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + tmp/demo MsgLeiosBlock tmp/my.db tmp/my.lfst Alice tmp/foo.bin + set +x + jq . tmp/my.lfst +done +sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +echo Done with EB bodies +rm tmp/reqs +# MsgLeiosBlockTxs messages +sqlite3 tmp/my.db 'SELECT ebId, MAX(txOffset) FROM ebTxs GROUP BY ebId' # dump sizes +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo ebId-to-point tmp/up.db -9223372036848484353 -9223372036843241473 | while IFS= read -r line; do + tmp/demo MsgLeiosBlockTxsOffer tmp/my.db tmp/my.lfst Alice $line +done +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo ebId-to-point tmp/up.db -9223372036848484353 -9223372036843241473 | while IFS= read -r line; do + tmp/demo MsgLeiosBlockTxsOffer tmp/my.db tmp/my.lfst Bob $line +done +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +jq . tmp/my.lfst +sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +set +x +cat tmp/reqs | grep -e MsgLeiosBlockTxsRequest | grep -e Alice | cut -d' ' -f4- | while IFS= read -r line; do + set -x + tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Alice tmp/foo.bin + set +x + jq . tmp/my.lfst + sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +done +cat tmp/reqs | grep -e MsgLeiosBlockTxsRequest | grep -e Bob | cut -d' ' -f4- | while IFS= read -r line; do + set -x + tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin + tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Bob tmp/foo.bin + jq . tmp/my.lfst + sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes + set +x +done From 5eca7c5298a2a4a73e066c78a930475fcc28fe1e Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 14:21:56 -0700 Subject: [PATCH 048/119] leiosdemo202510: small polishing pass --- ouroboros-consensus/app/leiosdemo202510.hs | 53 +++++++++++-------- ouroboros-consensus/ouroboros-consensus.cabal | 1 - script | 28 +++++----- 3 files changed, 43 insertions(+), 39 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 9817e93751..ca97695686 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -929,7 +929,6 @@ instance JSON.ToJSON HashBytes where instance JSON.ToJSONKey HashBytes where toJSONKey = hashBytesToText >$< JSON.toJSONKey --- | INVARIANT: no overlap data LeiosFetchState = MkLeiosFetchState { -- | Which EBs each peer has offered the body of -- @@ -938,7 +937,8 @@ data LeiosFetchState = MkLeiosFetchState { , -- | Which EBs each peer has offered the closure of -- - -- INVARIANT: every set of EBs all exactly agree about the claimed size of each tx + -- INVARIANT: all EBs from some peer exactly agree about the claimed size + -- of any txs they share (TODO enforce) -- -- TODO reverse index for when EBs age out? offeredEbTxs :: Map PeerId (Set EbId) @@ -946,16 +946,29 @@ data LeiosFetchState = MkLeiosFetchState { -- | EBs whose bodies have been received acquiredEbBodies :: Set EbId , - -- | EBs whose bodies have been offered but never received + -- | The size of each EB whose body has been offered but never received + -- + -- TODO double-check it won't actually be possible for peers to list + -- different sizes for the same EB, since 'EbId' will eventually be the + -- header hash, not the hash of the EB body? (It's the announcement that + -- specifies the EB body's hash.) missingEbBodies :: Map EbId BytesSize , - -- | Which requests have actually been sent to this peer + -- | Which requests have been sent to this peer + -- + -- (The fetch logic will not update this when it decides on some requests. + -- The LeiosFetch mini protocol clients update this when they actually send + -- those requests.) requestedPerPeer :: Map PeerId [LeiosFetchRequest] , - -- | INVARIANT: no empty sets + -- | Which peers have outstanding requests for which EB bodies + -- + -- INVARIANT: no empty sets requestedEbPeers :: Map EbId (Set PeerId) , - -- | INVARIANT: no empty sets + -- | Which peers have outstanding requests for which txs + -- + -- INVARIANT: no empty sets -- -- TODO may need to also store priority here requestedTxPeers :: Map TxHash (Set PeerId) @@ -1041,8 +1054,9 @@ type BytesSize = Int type TxHash = HashBytes -data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv - { +-- TODO which of these limits are allowed to be exceeded by at most one +-- request? +data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { -- | At most this many outstanding bytes requested from all peers together maxRequestedBytesSize :: Int , @@ -1061,8 +1075,10 @@ data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv -- TODO these maps are too big to actually have on the heap in the worst-case: -- 13888 txs per EB, 11000 EBs, 50 upstream peers, 32 bytes per hash -data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv - { +data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv { + -- | All missing txs in the context of EBs worth retrieving the closure for + ebBodies :: Map EbId (IntMap (TxHash, BytesSize)) + , -- | @slot -> hash -> EbId@ -- -- This relation is written to and loaded from the 'ebPoints' table on node @@ -1098,13 +1114,8 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv -- INVARIANT: @(ebPoints IntMap.! (ebIdSlot ebId)) Map.! (ebPointsInverse IntMap.! ebId) = ebId@ ebPointsInverse :: IntMap {- EbId -} HashBytes , --- acquiredTxBodies :: Map TxHash TxBytes --- , -- | Txs listed in received EBs but never themselves received missingTxBodies :: Set TxHash - , - -- | All missing txs in the context of EBs worth retrieving the closure for - ebBodies :: Map EbId (IntMap (TxHash, BytesSize)) , -- | Reverse index of 'ebBodies' -- @@ -1115,11 +1126,11 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv emptyLeiosFetchDynEnv :: LeiosFetchDynamicEnv emptyLeiosFetchDynEnv = MkLeiosFetchDynamicEnv + Map.empty IntMap.empty IntMap.empty Set.empty Map.empty - Map.empty loadLeiosFetchDynEnv :: DB.Database -> IO LeiosFetchDynamicEnv loadLeiosFetchDynEnv = loadLeiosFetchDynEnvHelper True @@ -1154,16 +1165,15 @@ loadLeiosFetchDynEnvHelper full db = do (Map.insertWith IntMap.union ebId (IntMap.singleton txOffset (txHash, txBytesSize)) bodies) (Map.insertWith Map.union txHash (Map.singleton ebId txOffset) offsetss) loop Set.empty Map.empty Map.empty - pure MkLeiosFetchDynamicEnv - { + pure MkLeiosFetchDynamicEnv { + ebBodies = bodies + , ebPoints = ps , ebPointsInverse = qs , missingTxBodies = missing , - ebBodies = bodies - , txOffsetss = offsetss } @@ -1492,8 +1502,7 @@ packRequests env dynEnv = fetchDecision2 :: DB.Database -> LeiosFetchState -> IO LeiosFetchState fetchDecision2 db acc0 = do - let env = MkLeiosFetchStaticEnv - { + let env = MkLeiosFetchStaticEnv { maxRequestedBytesSize = 50 * 10^(6 :: Int) , maxRequestedBytesSizePerPeer = 5 * 10^(6 :: Int) diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 21aa1aed28..105a24ab78 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -866,7 +866,6 @@ executable leiosdemo202510 direct-sqlite, directory, dlist, - ghc-prim, random, text, vector, diff --git a/script b/script index 861efac37e..eebca0f0b3 100755 --- a/script +++ b/script @@ -1,29 +1,28 @@ #! /bin/bash rm -f tmp/my.db tmp/up.db tmp/my.lfst tmp/demo tmp/reqBlocks tmp/reqBlockTxss -set -eux +set -eu cabal build exe:leiosdemo202510 ln -s $(cabal list-bin exe:leiosdemo202510) tmp/demo tmp/demo generate tmp/up.db tmp/myManifest.json -# MsgLeiosBlock messages sqlite3 tmp/up.db "SELECT ebSlot, PRINTF('%X', ebId), ebId FROM ebPoints ORDER BY ebId ASC" # dump points +echo ----- Receiving block offers from Alice sqlite3 tmp/up.db "SELECT PRINTF('%d %s', ebSlot, HEX(ebHashBytes)) FROM ebPoints ORDER BY ebId DESC" | while IFS= read -r line; do tmp/demo MsgLeiosBlockRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin sz=$(stat -c %s tmp/foo.bin) tmp/demo MsgLeiosBlockOffer tmp/my.db tmp/my.lfst Alice $line $sz done +echo ----- Receiving blocks from Alice tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs cat tmp/reqs | grep -e MsgLeiosBlockRequest | grep -e Alice | cut -d' ' -f4- | while IFS= read -r line; do - set -x tmp/demo MsgLeiosBlockRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin tmp/demo MsgLeiosBlock tmp/my.db tmp/my.lfst Alice tmp/foo.bin - set +x jq . tmp/my.lfst done -sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes +echo Incompletes; sqlite3 tmp/my.db 'SELECT ebId, SUM(1) FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs echo Done with EB bodies rm tmp/reqs -# MsgLeiosBlockTxs messages +echo ----- Receiving tx offers from Alice sqlite3 tmp/my.db 'SELECT ebId, MAX(txOffset) FROM ebTxs GROUP BY ebId' # dump sizes tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs tmp/demo ebId-to-point tmp/up.db -9223372036848484353 -9223372036843241473 | while IFS= read -r line; do @@ -31,27 +30,24 @@ tmp/demo ebId-to-point tmp/up.db -9223372036848484353 -9223372036843241473 | whi done tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs +echo ----- Receiving tx offers from Bob tmp/demo ebId-to-point tmp/up.db -9223372036848484353 -9223372036843241473 | while IFS= read -r line; do tmp/demo MsgLeiosBlockTxsOffer tmp/my.db tmp/my.lfst Bob $line done tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs tmp/demo fetch-logic-iteration tmp/my.db tmp/my.lfst | tee -a tmp/reqs jq . tmp/my.lfst -sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes -set +x +echo Incompletes; sqlite3 tmp/my.db 'SELECT ebId, SUM(1) FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' +echo ----- Receiving txs from Alice cat tmp/reqs | grep -e MsgLeiosBlockTxsRequest | grep -e Alice | cut -d' ' -f4- | while IFS= read -r line; do - set -x tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Alice tmp/foo.bin - set +x - jq . tmp/my.lfst - sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes + echo Incompletes; sqlite3 tmp/my.db 'SELECT ebId, SUM(1) FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' done +echo ----- Receiving txs from Bob cat tmp/reqs | grep -e MsgLeiosBlockTxsRequest | grep -e Bob | cut -d' ' -f4- | while IFS= read -r line; do - set -x tmp/demo MsgLeiosBlockTxsRequest tmp/up.db $line | xxd -plain -revert >tmp/foo.bin tmp/demo MsgLeiosBlockTxs tmp/my.db tmp/my.lfst Bob tmp/foo.bin - jq . tmp/my.lfst - sqlite3 tmp/my.db 'SELECT ebId FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' # dump incompletes - set +x + echo Incompletes; sqlite3 tmp/my.db 'SELECT ebId, SUM(1) FROM ebTxs WHERE txBytes IS NULL GROUP BY ebId' done +jq . tmp/my.lfst From bdee13cad8125df2dfc6322136dcb6c03eb9866a Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 14:46:27 -0700 Subject: [PATCH 049/119] leiosdemo202510: also insert into TxCache --- ouroboros-consensus/app/leiosdemo202510.hs | 32 ++++++++++++++-------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index ca97695686..89167377ba 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -705,12 +705,11 @@ msgLeiosBlockTxs db lfst0 peerId ebTxsPath = do _ -> die "Not expecting MsgLeiosBlockTxs" ebId <- ebIdFromPoint' db ebSlot (let MkHashBytes x = ebHash in x) ebTxsBytes <- BSL.readFile ebTxsPath - stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebTx) - withDie $ DB.bindInt64 stmt 2 (fromIntegralEbId ebId) + stmtTxCache <- withDieJust $ DB.prepare db (fromString sql_insert_txCache) + stmtEbTxs <- withDieJust $ DB.prepare db (fromString sql_update_ebTx) + withDie $ DB.bindInt64 stmtEbTxs 2 (fromIntegralEbId ebId) withDieMsg $ DB.exec db (fromString "BEGIN") - -- decode incrementally and simultaneously UPDATE ebTxs - -- - -- TODO also INSERT INTO TxCache + -- decode incrementally and simultaneously UPDATE ebTxs and INSERT INTO txCache let decodeBreakOrTx = do stop <- CBOR.decodeBreakOr if stop then pure Nothing else Just <$> CBOR.decodeBytes @@ -736,10 +735,16 @@ msgLeiosBlockTxs db lfst0 peerId ebTxsPath = do (txOffset:offsets', Just txHash) | txHash /= MkHashBytes (Hash.hashToBytes txHash') -> die "Wrong tx hash" | otherwise -> do - withDie $ DB.bindInt64 stmt 3 $ fromIntegral txOffset - withDie $ DB.bindBlob stmt 1 $ serialize' $ CBOR.encodeBytes txBytes - withDieDone $ DB.stepNoCB stmt - withDie $ DB.reset stmt + -- INTO ebTxs + withDie $ DB.bindInt64 stmtEbTxs 3 $ fromIntegral txOffset + withDie $ DB.bindBlob stmtEbTxs 1 $ serialize' $ CBOR.encodeBytes txBytes + withDieDone $ DB.stepNoCB stmtEbTxs + withDie $ DB.reset stmtEbTxs + -- INTO txCache + withDie $ DB.bindBlob stmtTxCache 1 $ Hash.hashToBytes txHash' + withDie $ DB.bindBlob stmtTxCache 2 $ serialize' $ CBOR.encodeBytes txBytes + withDieDone $ DB.stepNoCB stmtTxCache + withDie $ DB.reset stmtTxCache go1 (Map.update (delIfNull . Set.delete peerId) txHash accRequested) (accTxBytesSize + txBytesSize) @@ -776,13 +781,18 @@ msgLeiosBlockTxs db lfst0 peerId ebTxsPath = do requestedTxPeers = requested' } -sql_insert_ebTx :: String -sql_insert_ebTx = +sql_update_ebTx :: String +sql_update_ebTx = "UPDATE ebTxs\n\ \SET txBytes = ?\n\ \WHERE ebId = ? AND txOffset = ? AND txBytes IS NULL\n\ \" +sql_insert_txCache :: String +sql_insert_txCache = + "INSERT OR IGNORE INTO txCache (txHashBytes, txBytes, expiryUnixEpoch) VALUES (?, ?, -1)\n\ + \" + ----- {- From e7e31048efcf00087bdd609f7fec5a665ea05063 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 15:32:05 -0700 Subject: [PATCH 050/119] leiosdemo202510: do not fetch txs already in TxCache --- ouroboros-consensus/app/leiosdemo202510.hs | 138 ++++++++++++++------- 1 file changed, 92 insertions(+), 46 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 89167377ba..c7f7dc5831 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -34,7 +34,7 @@ import Data.IntMap (IntMap) import Data.List (intercalate, isSuffixOf, unfoldr) import Data.Map (Map) import Data.Maybe (fromMaybe) -import qualified Data.Map as Map +import qualified Data.Map.Strict as Map import Data.Set (Set) import qualified Data.Set as Set import Data.String (fromString) @@ -991,7 +991,17 @@ data LeiosFetchState = MkLeiosFetchState { -- | Sum of 'requestedBytesSizePerPeer' -- -- INVARIANT: @<= maxRequestedBytesSize@ - requestedBytesSize :: BytesSize + requestedBytesSize :: !BytesSize + , + -- | The 'EbId', offsets, and sizes of txs that need to be copied from the + -- TxCache to the EbStore + toCopy :: Map EbId (IntMap BytesSize) + , + -- | INVARIANT: @sum $ fmap sum 'toCopy'@ + toCopyBytesSize :: !BytesSize + , + -- | INVARIANT: @sum $ fmap IntMap.size 'toCopy'@ + toCopyCount :: !Int } deriving (Generic) @@ -1013,6 +1023,9 @@ emptyLeiosFetchState = Map.empty Map.empty 0 + Map.empty + 0 + 0 ebIdSlot :: EbId -> Word64 ebIdSlot (MkEbId y) = @@ -1068,24 +1081,33 @@ type TxHash = HashBytes -- request? data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { -- | At most this many outstanding bytes requested from all peers together - maxRequestedBytesSize :: Int + maxRequestedBytesSize :: BytesSize , -- | At most this many outstanding bytes requested from each peer - maxRequestedBytesSizePerPeer :: Int + maxRequestedBytesSizePerPeer :: BytesSize , -- | At most this many outstanding bytes per request - maxRequestBytesSize :: Int + maxRequestBytesSize :: BytesSize , -- | At most this many outstanding requests for each EB body maxRequestsPerEb :: Int , -- | At most this many outstanding requests for each individual tx maxRequestsPerTx :: Int + , + -- | At most this many bytes are scheduled to be copied from the TxCache to the EbStore + maxToCopyBytesSize :: BytesSize + , + -- | At most this many txs are scheduled to be copied from the TxCache to the EbStore + maxToCopyCount :: Int } -- TODO these maps are too big to actually have on the heap in the worst-case: -- 13888 txs per EB, 11000 EBs, 50 upstream peers, 32 bytes per hash data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv { + -- | The size of every tx in the TxCache + cachedTxs :: Map TxHash BytesSize + , -- | All missing txs in the context of EBs worth retrieving the closure for ebBodies :: Map EbId (IntMap (TxHash, BytesSize)) , @@ -1136,6 +1158,7 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv { emptyLeiosFetchDynEnv :: LeiosFetchDynamicEnv emptyLeiosFetchDynEnv = MkLeiosFetchDynamicEnv + Map.empty Map.empty IntMap.empty IntMap.empty @@ -1160,6 +1183,16 @@ loadLeiosFetchDynEnvHelper full db = do (IntMap.insertWith Map.union ebSlot (Map.singleton ebHash (MkEbId ebId)) ps) (IntMap.insert ebId ebHash qs) loop IntMap.empty IntMap.empty + cached <- if not full then pure Map.empty else do + stmt <- withDieJust $ DB.prepare db (fromString sql_scan_txCache) + let loop !cached = + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> pure cached + DB.Row -> do + txHashBytes <- MkHashBytes <$> DB.columnBlob stmt 0 + txBytesSize <- fromIntegral <$> DB.columnInt64 stmt 1 + loop (Map.insert txHashBytes txBytesSize cached) + loop Map.empty (missing, bodies, offsetss) <- if not full then pure (Set.empty, Map.empty, Map.empty) else do stmt <- withDieJust $ DB.prepare db (fromString sql_scan_missingEbTx) let loop !missing !bodies !offsetss = @@ -1176,6 +1209,8 @@ loadLeiosFetchDynEnvHelper full db = do (Map.insertWith Map.union txHash (Map.singleton ebId txOffset) offsetss) loop Set.empty Map.empty Map.empty pure MkLeiosFetchDynamicEnv { + cachedTxs = cached + , ebBodies = bodies , ebPoints = ps @@ -1202,6 +1237,13 @@ sql_scan_missingEbTx = \ORDER BY ebId DESC, txOffset ASC\n\ \" +sql_scan_txCache :: String +sql_scan_txCache = + "SELECT txHashBytes\n\ + \FROM txCache\n\ + \ORDER BY txHashBytes\n\ + \" + ----- newtype LeiosFetchDecisions = @@ -1209,6 +1251,9 @@ newtype LeiosFetchDecisions = (Map PeerId (Map Word64 (DList (TxHash, BytesSize, Map EbId Int), DList EbId))) deriving (Show) +emptyLeiosFetchDecisions :: LeiosFetchDecisions +emptyLeiosFetchDecisions = MkLeiosFetchDecisions Map.empty + leiosFetchLogicIteration :: LeiosFetchStaticEnv -> @@ -1219,16 +1264,16 @@ leiosFetchLogicIteration :: (LeiosFetchState, LeiosFetchDecisions) leiosFetchLogicIteration env dynEnv = \acc -> - go1 acc (MkLeiosFetchDecisions Map.empty) + go1 acc emptyLeiosFetchDecisions $ expand $ Map.toDescList $ Map.map Left (missingEbBodies acc) `Map.union` Map.map Right (ebBodies dynEnv) where expand = \case [] -> [] - (ebId, Left ebByteSize):vs -> Left (ebId, ebByteSize) : expand vs + (ebId, Left ebBytesSize):vs -> Left (ebId, ebBytesSize) : expand vs (ebId, Right v):vs -> - [ Right (ebId, txHash) | (txHash, _txBytesSize) <- IntMap.elems v ] + [ Right (ebId, txOffset, txHash) | (txOffset, (txHash, _txBytesSize)) <- IntMap.toAscList v ] <> expand vs go1 !acc !accNew = \case [] @@ -1239,18 +1284,39 @@ leiosFetchLogicIteration env dynEnv = peerIds = Map.findWithDefault Set.empty ebId (requestedEbPeers acc) -> goEb2 acc accNew targets ebId ebBytesSize peerIds - Right (ebId, txHash) : targets + Right (ebId, txOffset, txHash) : targets + + | not $ Set.member txHash (missingTxBodies dynEnv) -- we already have it + -> go1 acc accNew targets + + | Just _ <- Map.lookup ebId (toCopy acc) >>= IntMap.lookup txOffset + -- it's already scheduled to be copied from TxCache + -> go1 acc accNew targets + + | Just txBytesSize <- Map.lookup txHash (cachedTxs dynEnv) -- it's in the TxCache + -> let full = + toCopyBytesSize acc >= maxToCopyBytesSize env + || + toCopyCount acc >= maxToCopyCount env + acc' = + if full then acc else + acc { + toCopy = Map.insertWith IntMap.union ebId (IntMap.singleton txOffset txBytesSize) (toCopy acc) + , + toCopyBytesSize = toCopyBytesSize acc + txBytesSize + , + toCopyCount = toCopyCount acc + 1 + } + in go1 acc' accNew targets - | Set.member txHash (missingTxBodies dynEnv) -- we don't already have it - , let !txOffsets = case Map.lookup txHash (txOffsetss dynEnv) of + | otherwise + -> let !txOffsets = case Map.lookup txHash (txOffsetss dynEnv) of Nothing -> error "impossible!" Just x -> x - , let peerIds :: Set PeerId + peerIds :: Set PeerId peerIds = Map.findWithDefault Set.empty txHash (requestedTxPeers acc) - -> goTx2 acc accNew targets (ebIdSlot ebId) txHash txOffsets peerIds - - | otherwise - -> go1 acc accNew targets + in + goTx2 acc accNew targets (ebIdSlot ebId) txHash txOffsets peerIds goEb2 !acc !accNew targets ebId ebBytesSize peerIds | requestedBytesSize acc >= maxRequestedBytesSize env -- we can't request anything @@ -1262,24 +1328,12 @@ leiosFetchLogicIteration env dynEnv = = let accNew' = MkLeiosFetchDecisions $ Map.insertWith - (Map.unionWith (<>)) - peerId - (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton ebId)) - (let MkLeiosFetchDecisions x = accNew in x) - acc' = MkLeiosFetchState { - offeredEbs = offeredEbs acc - , - offeredEbTxs = offeredEbTxs acc - , - acquiredEbBodies = acquiredEbBodies acc - , - missingEbBodies = missingEbBodies acc - , - requestedPerPeer = requestedPerPeer acc - , + (Map.unionWith (<>)) + peerId + (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton ebId)) + (let MkLeiosFetchDecisions x = accNew in x) + acc' = acc { requestedEbPeers = Map.insertWith Set.union ebId (Set.singleton peerId) (requestedEbPeers acc) - , - requestedTxPeers = requestedTxPeers acc , requestedBytesSizePerPeer = Map.insertWith (+) peerId ebBytesSize (requestedBytesSizePerPeer acc) , @@ -1327,19 +1381,7 @@ leiosFetchLogicIteration env dynEnv = peerId (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'), DList.empty)) (let MkLeiosFetchDecisions x = accNew in x) - acc' = MkLeiosFetchState { - offeredEbs = offeredEbs acc - , - offeredEbTxs = offeredEbTxs acc - , - acquiredEbBodies = acquiredEbBodies acc - , - missingEbBodies = missingEbBodies acc - , - requestedPerPeer = requestedPerPeer acc - , - requestedEbPeers = requestedEbPeers acc - , + acc' = acc { requestedTxPeers = Map.insertWith Set.union txHash (Set.singleton peerId) (requestedTxPeers acc) , requestedBytesSizePerPeer = Map.insertWith (+) peerId txBytesSize (requestedBytesSizePerPeer acc) @@ -1522,6 +1564,10 @@ fetchDecision2 db acc0 = do maxRequestsPerEb = 2 , maxRequestsPerTx = 2 + , + maxToCopyBytesSize = 100 * 2^(20 :: Int) + , + maxToCopyCount = 100 * 10^(3 :: Int) } dynEnv <- loadLeiosFetchDynEnv db let (acc1, MkLeiosFetchDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 From 3d5487e8d9c43df65a1c8a69fd124666467c11b6 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 18:45:24 -0700 Subject: [PATCH 051/119] leiosdemo202510: add cache-copy command --- ouroboros-consensus/app/leiosdemo202510.hs | 89 +++++++++++++++++++++- 1 file changed, 87 insertions(+), 2 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index c7f7dc5831..e027860c7b 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -153,6 +153,16 @@ main2 = getArgs >>= \case | ".bin" `isSuffixOf` ebTxsPath -> do hashTxs ebTxsPath + ["cache-copy", dbPath, lfstPath, bytesSizeStr] + | ".db" `isSuffixOf` dbPath + , ".lfst" `isSuffixOf` lfstPath + , Just bytesSize <- readMaybe bytesSizeStr + , 0 < bytesSize + -> do + db <- reopenDb dbPath + acc <- withDiePoly id $ JSON.eitherDecodeFileStrict lfstPath + acc' <- doCacheCopy db acc bytesSize + JSON.encodeFile lfstPath acc' _ -> die "Either $0 generate my.db myManifest.json\n\ \ OR $0 ebId-to-point my.db ebId ebId ebId...\n\ @@ -164,6 +174,7 @@ main2 = getArgs >>= \case \ OR $0 MsgLeiosBlockTxs my.db my.lfst peerId myEbTxs.bin\n\ \ OR $0 fetch-logic-iteration my.db my.lfst\n\ \ OR $0 hash-txs myEbTxs.bin\n\ + \ OR $0 cache-copy my.db my.lfst bytesSize(positive)\n\ \" reopenDb :: FilePath -> IO DB.Database @@ -323,6 +334,8 @@ sql_schema = \ ,\n\ \ txBytes BLOB NOT NULL -- valid CBOR\n\ \ ,\n\ + \ txBytesSize INTEGER NOT NULL\n\ + \ ,\n\ \ expiryUnixEpoch INTEGER NOT NULL\n\ \ ) WITHOUT ROWID;\n\ \\n\ @@ -743,6 +756,7 @@ msgLeiosBlockTxs db lfst0 peerId ebTxsPath = do -- INTO txCache withDie $ DB.bindBlob stmtTxCache 1 $ Hash.hashToBytes txHash' withDie $ DB.bindBlob stmtTxCache 2 $ serialize' $ CBOR.encodeBytes txBytes + withDie $ DB.bindInt64 stmtTxCache 3 $ fromIntegral txBytesSize withDieDone $ DB.stepNoCB stmtTxCache withDie $ DB.reset stmtTxCache go1 @@ -790,7 +804,7 @@ sql_update_ebTx = sql_insert_txCache :: String sql_insert_txCache = - "INSERT OR IGNORE INTO txCache (txHashBytes, txBytes, expiryUnixEpoch) VALUES (?, ?, -1)\n\ + "INSERT OR IGNORE INTO txCache (txHashBytes, txBytes, txBytesSize, expiryUnixEpoch) VALUES (?, ?, ?, -1)\n\ \" ----- @@ -1239,7 +1253,7 @@ sql_scan_missingEbTx = sql_scan_txCache :: String sql_scan_txCache = - "SELECT txHashBytes\n\ + "SELECT txHashBytes, txBytesSize\n\ \FROM txCache\n\ \ORDER BY txHashBytes\n\ \" @@ -1632,3 +1646,74 @@ delIfNull x = if Set.null x then Nothing else Just x delIfZero :: (Eq a, Num a) => a -> Maybe a delIfZero x = if 0 == x then Nothing else Just x + +----- + +doCacheCopy :: DB.Database -> LeiosFetchState -> BytesSize -> IO LeiosFetchState +doCacheCopy db lfst bytesSize = do + withDieMsg $ DB.exec db (fromString sql_attach_ebIds) + withDieMsg $ DB.exec db (fromString "BEGIN") + stmt <- withDieJust $ DB.prepare db (fromString sql_insert_memEbIds) + -- load in-mem table of ebId-txOffset pairs + lfst' <- go1 stmt 0 0 (toCopy lfst) + -- UPDATE JOIN driven by the loaded table + withDieMsg $ DB.exec db (fromString sql_copy_from_txCache) + withDieMsg $ DB.exec db (fromString "COMMIT") + pure lfst' + where + go1 stmt !accBytesSize !accCount !acc + | accBytesSize < bytesSize + , Just ((ebId, txs), acc') <- Map.maxViewWithKey acc + = go2 stmt accBytesSize accCount acc' ebId txs + + | otherwise + = finish accBytesSize accCount acc + + go2 stmt !accBytesSize !accCount !acc ebId txs + | Just ((txOffset, txBytesSize), txs') <- IntMap.minViewWithKey txs + = if accBytesSize + txBytesSize > bytesSize then stop else do + withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) + withDie $ DB.bindInt64 stmt 2 (fromIntegral txOffset) + withDieDone $ DB.stepNoCB stmt + withDie $ DB.reset stmt + go2 stmt (accBytesSize + txBytesSize) (accCount + 1) acc ebId txs' + | otherwise + = go1 stmt accBytesSize accCount acc + where + stop = finish accBytesSize accCount $ if IntMap.null txs then acc else Map.insert ebId txs acc + + finish accBytesSize accCount acc = + pure lfst { + toCopy = acc + , + toCopyBytesSize = toCopyBytesSize lfst - accBytesSize + , + toCopyCount = toCopyCount lfst - accCount + } + +sql_attach_ebIds :: String +sql_attach_ebIds = + -- NB :memory: databases are discarded when the SQLite connection is closed + "ATTACH DATABASE ':memory:' AS mem;\n\ + \\n\ + \CREATE TABLE mem.ebIds (\n\ + \ ebId INTEGER NOT NULL\n\ + \ ,\n\ + \ txOffset INTEGER NOT NULL\n\ + \ ,\n\ + \ PRIMARY KEY (ebId ASC, txOffset ASC)\n\ + \ ) WITHOUT ROWID;\n\ + \" + +sql_insert_memEbIds :: String +sql_insert_memEbIds = + "INSERT INTO mem.ebIds (ebId, txOffset) VALUES (?, ?);\n\ + \" + +sql_copy_from_txCache :: String +sql_copy_from_txCache = + "UPDATE ebTxs\n\ + \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = x.txHashBytes)\n\ + \FROM ebTxs AS x\n\ + \INNER JOIN mem.ebIds ON x.ebId = mem.ebIds.ebId AND x.txOffset = mem.ebIds.txOffset\n\ + \" From ccbe69384bd3d352dc5d31ed31d5edac255a2a8f Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Thu, 23 Oct 2025 18:45:57 -0700 Subject: [PATCH 052/119] leiosdemo202510: rename binder to nickname in myManifest.json --- myManifest.json | 6 +++--- ouroboros-consensus/app/leiosdemo202510.hs | 13 +++++++------ 2 files changed, 10 insertions(+), 9 deletions(-) diff --git a/myManifest.json b/myManifest.json index a7e48099e3..721b82b99d 100644 --- a/myManifest.json +++ b/myManifest.json @@ -1,15 +1,15 @@ [ {"slotNo": 5, "txRecipes": [55, 55, 55, 1000]} , - {"slotNo": 10, "binder": "SmallA", "txRecipes": [100, 200, 300]} + {"slotNo": 10, "nickname": "SmallA", "txRecipes": [100, 200, 300]} , - {"slotNo": 11, "txRecipes": [{"share": "SmallA", "startIncl": 0}, 400]} + {"slotNo": 11, "nickname": "SmallB", "txRecipes": [{"share": "SmallA", "startIncl": 0}, 400]} , {"slotNo": 15, "comment": "closure = 12.5 megabyte, minimal EB", "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } , - {"slotNo": 20, "binder": "BigA", "comment": "closure = 12.5 megabyte, maximal EB under 0.5 megabyte", "txRecipes": + {"slotNo": 20, "nickname": "BigA", "comment": "closure = 12.5 megabyte, maximal EB under 0.5 megabyte", "txRecipes": [ 1398, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, 925, diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index e027860c7b..1b073440b8 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -201,7 +201,7 @@ prettyBitmap (idx, bitmap) = show idx ++ ":0x" ++ Numeric.showHex bitmap "" data EbRecipe = EbRecipe { - ebRecipeBinder :: Maybe String + ebRecipeNickname :: Maybe String , ebRecipeElems :: V.Vector EbRecipeElem , @@ -211,7 +211,7 @@ data EbRecipe = EbRecipe { instance JSON.FromJSON EbRecipe where parseJSON = JSON.withObject "EbRecipe" $ \v -> EbRecipe - <$> v JSON..:? (fromString "binder") + <$> v JSON..:? (fromString "nickname") <*> v JSON..: (fromString "txRecipes") <*> v JSON..: (fromString "slotNo") @@ -244,7 +244,7 @@ generateDb prng0 db ebRecipes = do stmt_write_ebId <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) - (_dynEnv', _sigma) <- (\f -> foldM f (emptyLeiosFetchDynEnv, Map.empty) ebRecipes) $ \(dynEnv, sigma) ebRecipe -> do + (_dynEnv', sigma) <- (\f -> foldM f (emptyLeiosFetchDynEnv, Map.empty) ebRecipes) $ \(dynEnv, sigma) ebRecipe -> do -- generate txs, so we have their hashes let finishX (n, x) = V.fromListN n $ Foldable.toList $ revX x -- TODO in ST with mut vector txs <- fmap finishX $ (\f -> V.foldM f (0, emptyX) (ebRecipeElems ebRecipe)) $ \(accN, accX) -> \case @@ -320,10 +320,11 @@ generateDb prng0 db ebRecipes = do withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") - pure (fromMaybe dynEnv mbDynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeBinder ebRecipe) sigma) + pure (fromMaybe dynEnv mbDynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeNickname ebRecipe) sigma) -- finalize db withDieMsg $ DB.exec db (fromString sql_index_schema) - -- TODO maybe print out the @sigma@ mapping as JSON, so the user can see the EbId for each of their declared variables? + forM_ (Map.toList sigma) $ \(nickname, (ebId, _count)) -> do + putStrLn $ unwords [nickname, prettyEbId ebId] ----- @@ -630,7 +631,7 @@ sql_lookup_ebClosures_DESC n = \ORDER BY txOffset DESC\n\ \" where - hooks = intercalate ", " (replicate n "?") + hooks = intercalate "," (replicate n "?") ----- From 2dafd96206843ba4bdf5e7f9e1d8c6be3cf797f3 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Fri, 24 Oct 2025 10:49:51 +0200 Subject: [PATCH 053/119] Set all followert instructions to blocking There's many rollback events that happen on the last block. --- .../Cardano/Tools/ImmDBServer/MiniProtocols.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 7d71840bdb..9f8a2178fe 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -222,7 +222,7 @@ chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ d pure $ Just pt pure Follower { - followerInstruction = Just <$> followerInstructionBlocking + followerInstruction = pure Nothing , followerInstructionBlocking , followerForward , followerClose From f69528baa8644593a8e5c952d0e41062d047dba8 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Fri, 24 Oct 2025 11:47:34 +0200 Subject: [PATCH 054/119] Cosmetic changes to aid my own comprehension --- .../app/immdb-server.hs | 22 +++++-------------- 1 file changed, 6 insertions(+), 16 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index 60630bfa2e..c37b057baf 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -1,6 +1,7 @@ {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} module Main (main) where @@ -19,7 +20,6 @@ import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) import Cardano.Slotting.Slot (SlotNo (..), WithOrigin (At, Origin)) import qualified Data.Time.Clock.POSIX as POSIX import Data.Time.Clock (DiffTime) -import Data.Int (Int64) main :: IO () main = withStdTerminalHandles $ do @@ -48,19 +48,12 @@ main = withStdTerminalHandles $ do mkGetSlotDelay :: SlotNo -> POSIX.POSIXTime -> WithOrigin SlotNo -> IO DiffTime mkGetSlotDelay refSlotNr refTimeForRefSlot = -- If slot < refSlotNr, we need to subtract to - -- refTimeForRefSlot. To simplify the calculations we work - -- with Int64 - let iRefSlotNr :: Int64 - iRefSlotNr = fromIntegral $ unSlotNo refSlotNr - - -- TODO: here is where we assume the slot duration of 1 second. - toSeconds :: Int64 -> POSIX.POSIXTime - toSeconds iSlot = realToFrac iSlot + -- refTimeForRefSlot. + let slotToPosix :: SlotNo -> POSIX.POSIXTime + slotToPosix slot = fromIntegral . unSlotNo $ slot -- TODO: here is where we assume the slot duration of 1 second. in \case Origin -> pure 0 -- TODO: I'm not sure what we want to do here. At slot -> do - let iSlot = fromIntegral $ unSlotNo slot - slotTime = refTimeForRefSlot + toSeconds (iSlot - iRefSlotNr) - + let slotTime = refTimeForRefSlot + (slotToPosix slot - slotToPosix refSlotNr) currentTime <- POSIX.getPOSIXTime pure $ if currentTime <= slotTime then realToFrac $ slotTime - currentTime @@ -114,12 +107,9 @@ optsParser = , help "Reference slot number (SlotNo). This, together with the initial-time will be used for time translations." , metavar "SLOT_NO" ] - refTimeForRefSlot <- fmap asPOSIXseconds $ option auto $ mconcat + refTimeForRefSlot <- fmap (fromInteger @POSIX.POSIXTime) $ option auto $ mconcat [ long "initial-time" , help "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)" , metavar "POSIX_SECONDS" ] pure Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot} - where - asPOSIXseconds :: Double -> POSIX.POSIXTime - asPOSIXseconds = realToFrac From f0e793ff6947805514bfd81f876c9e1b100fd941 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Fri, 24 Oct 2025 12:35:40 +0200 Subject: [PATCH 055/119] Switch to using plotly for charting events --- scripts/leios-demo/build.nix | 1 + scripts/leios-demo/demo_analysis.ipynb | 75 ++++++++++++++------------ scripts/leios-demo/requirements.txt | 1 + 3 files changed, 42 insertions(+), 35 deletions(-) diff --git a/scripts/leios-demo/build.nix b/scripts/leios-demo/build.nix index de2c1f4ed0..82467d8599 100644 --- a/scripts/leios-demo/build.nix +++ b/scripts/leios-demo/build.nix @@ -20,6 +20,7 @@ widgetsnbextension jupyterlab jupyter + plotly nixpkgs-fmt nil diff --git a/scripts/leios-demo/demo_analysis.ipynb b/scripts/leios-demo/demo_analysis.ipynb index c6f0fee61a..0fdbb7a6fd 100644 --- a/scripts/leios-demo/demo_analysis.ipynb +++ b/scripts/leios-demo/demo_analysis.ipynb @@ -22,10 +22,13 @@ "import json\n", "import pandas as pd\n", "import altair as alt\n", - "from itables import init_notebook_mode\n", + "import itables as itables\n", "import ipywidgets as widgets\n", + "import plotly.offline as plotly\n", + "import plotly.express as px\n", "\n", - "init_notebook_mode(all_interactive=True)" + "plotly.init_notebook_mode(connected=True) \n", + "itables.init_notebook_mode(all_interactive=True)" ] }, { @@ -53,13 +56,32 @@ " at_lines = [ json.loads(line) for line in lines if line.startswith('{\"at') ]\n", " return pd.DataFrame.from_records(at_lines)\n", "\n", - "def events_chart(df, eventPrefix):\n", - " return alt.Chart(df[df.ns.str.startswith(eventPrefix)].reset_index()).mark_point().encode(\n", - " x='at:T',\n", - " y='source',\n", - " color='ns',\n", - " tooltip='ns'\n", - " ).interactive()\n", + "\n", + "def events_chart(df, y, color):\n", + " fig = px.scatter(\n", + " df, \n", + " x='at', \n", + " y=y, \n", + " color=color, # Optional: Group events by color\n", + " title='Event chart',\n", + " hover_data=['data'] # Show event name on hover\n", + " )\n", + "\n", + " # Add the Range Slider and Range Selector Buttons\n", + " fig.update_xaxes(\n", + " # Enable the Range Slider below the chart\n", + " rangeslider_visible=True,\n", + " \n", + " # Add preset buttons for easy selection (e.g., 1 month, 6 months)\n", + " rangeselector=dict(\n", + " buttons=list([\n", + " dict(count=1, label=\"1M\", step=\"month\", stepmode=\"backward\"),\n", + " dict(count=6, label=\"6M\", step=\"month\", stepmode=\"backward\"),\n", + " dict(step=\"all\", label=\"ALL\")\n", + " ])\n", + " )\n", + " )\n", + " return fig\n", "\n", "cardano_node_0_df = df_from_cardano_node_logs(\"data/cardano-node-0.log\")\n", "cardano_node_1_df = df_from_cardano_node_logs(\"data/cardano-node-1.log\")\n", @@ -93,9 +115,9 @@ }, "outputs": [], "source": [ - "# ChainSync events\n", + "# Events\n", "\n", - "events_chart(all_df, 'ChainSync')" + "events_chart(all_df, 'source', 'ns')" ] }, { @@ -110,7 +132,7 @@ "outputs": [], "source": [ "# SELECT * FROM all_df WHERE sev = 'Error'\n", - "display(events_chart(all_df[all_df.sev == \"Error\"], \"\"))\n", + "display(events_chart(all_df[all_df.sev == \"Error\"], \"source\", \"ns\"))\n", "all_df[all_df.sev == \"Error\"]" ] }, @@ -134,33 +156,16 @@ }, { "cell_type": "markdown", - "id": "76191267-de35-47c0-ba9d-90276a552c13", + "id": "3f5d9494-7f67-47fc-b356-dc6db95f6b7b", "metadata": {}, "source": [ - "## Latency" - ] - }, - { - "cell_type": "code", - "execution_count": null, - "id": "147ede1a-0363-434d-bea8-e1f51219a56f", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, - "outputs": [], - "source": [ - "latency_logs_df = all_df[all_df.ns.isin([\"BlockFetch.Client.CompletedBlockFetch\", \"ChainSync.Client.DownloadedHeader\"])]\n", - "latency_logs_df = latency_logs_df.assign(\n", - " block=latency_logs_df.data.apply(lambda r: r['block']),\n", - ")" + "## Block related logs" ] }, { "cell_type": "code", "execution_count": null, - "id": "8892142d-3487-4b9e-a0cc-a1cebdc77df6", + "id": "54fdda99-554a-4bc3-8a9e-fb346487f4ed", "metadata": { "jupyter": { "source_hidden": true @@ -168,9 +173,9 @@ }, "outputs": [], "source": [ - "latency_logs_df.groupby(['block', 'source', 'ns']).agg({\n", - " 'at': ['count', 'min', 'max']\n", - "})" + "block_df = all_df[all_df.data.apply(lambda r: 'block' in r)]\n", + "\n", + "events_chart(block_df, \"source\", \"ns\")" ] } ], diff --git a/scripts/leios-demo/requirements.txt b/scripts/leios-demo/requirements.txt index 9a2152851d..88713ee751 100644 --- a/scripts/leios-demo/requirements.txt +++ b/scripts/leios-demo/requirements.txt @@ -76,6 +76,7 @@ parso==0.8.4 pathspec==0.12.1 pexpect==4.9.0 platformdirs==4.3.8 +plotly==6.3.0 pluggy==1.6.0 ply==3.11 prometheus_client==0.22.1 From 58abd619d96363c27333154bff150c892b0cdec1 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 07:31:32 -0700 Subject: [PATCH 056/119] leiosdemo202510: add mini protocol stubs to ImmDB server --- .../Tools/ImmDBServer/MiniProtocols.hs | 13 +++++++ .../Ouroboros/Consensus/Network/NodeToNode.hs | 39 +++++++++---------- ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../LeiosDemoOnlyTestFetch.hs | 5 +++ .../LeiosDemoOnlyTestNotify.hs | 5 +++ 5 files changed, 43 insertions(+), 20 deletions(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 9f8a2178fe..617fbdd355 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -61,6 +61,9 @@ import Ouroboros.Network.Protocol.Handshake.Version (Version (..)) import Ouroboros.Network.Protocol.KeepAlive.Server (keepAliveServerPeer) +import LeiosDemoOnlyTestFetch +import LeiosDemoOnlyTestNotify + immDBServer :: forall m blk addr. ( IOLike m @@ -125,6 +128,16 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay = do N2N.txSubmissionMiniProtocolNum N2N.txSubmissionProtocolLimits txSubmissionProt + , mkMiniProtocol + Mux.StartOnDemand + leiosNotifyMiniProtocolNum + (const Consensus.N2N.leiosNotifyProtocolLimits) + undefined + , mkMiniProtocol + Mux.StartOnDemand + leiosFetchMiniProtocolNum + (const Consensus.N2N.leiosFetchProtocolLimits) + undefined ] where Consensus.N2N.Codecs { diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 369ec21676..a3beebcff2 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -34,6 +34,9 @@ module Ouroboros.Consensus.Network.NodeToNode ( , initiatorAndResponder -- * Re-exports , ChainSyncTimeout (..) + + , leiosFetchProtocolLimits + , leiosNotifyProtocolLimits ) where import Codec.CBOR.Decoding (Decoder) @@ -125,6 +128,8 @@ import Ouroboros.Network.TxSubmission.Outbound import qualified Ouroboros.Network.Mux as ON +import LeiosDemoOnlyTestFetch (leiosFetchMiniProtocolNum) +import LeiosDemoOnlyTestNotify (leiosNotifyMiniProtocolNum) {------------------------------------------------------------------------------- Handlers @@ -845,23 +850,17 @@ initiator miniProtocolParameters version versionData Apps {..} = ON.MiniProtocol { ON.miniProtocolNum = leiosNotifyMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, - ON.miniProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte - }, + ON.miniProtocolLimits = leiosNotifyProtocolLimits, ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) } , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, - ON.miniProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes - }, + ON.miniProtocolLimits = leiosFetchProtocolLimits, ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) } ] } - where - addSafetyMargin x = x + x `div` 10 -- | A bi-directional network application. -- @@ -907,27 +906,27 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = ON.MiniProtocol { ON.miniProtocolNum = leiosNotifyMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, - ON.miniProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte - }, + ON.miniProtocolLimits = leiosNotifyProtocolLimits, ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) } , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, - ON.miniProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes - }, + ON.miniProtocolLimits = leiosFetchProtocolLimits, ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) } ] } - where - addSafetyMargin x = x + x `div` 10 +leiosNotifyProtocolLimits :: MiniProtocolLimits +leiosNotifyProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte + } -leiosNotifyMiniProtocolNum :: MiniProtocolNum -leiosNotifyMiniProtocolNum = MiniProtocolNum 18 +leiosFetchProtocolLimits :: MiniProtocolLimits +leiosFetchProtocolLimits = ON.MiniProtocolLimits { + ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes + } -leiosFetchMiniProtocolNum :: MiniProtocolNum -leiosFetchMiniProtocolNum = MiniProtocolNum 19 +addSafetyMargin :: Int -> Int +addSafetyMargin x = x + x `div` 10 diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 105a24ab78..cca1bb4a7c 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -327,6 +327,7 @@ library monoid-subclasses, mtl, multiset ^>=0.3, + network-mux ^>=0.8, nothunks ^>=0.2, ouroboros-network-api ^>=0.14, ouroboros-network-mock ^>=0.1, diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 484acea684..058ff4d0a1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -19,6 +19,7 @@ module LeiosDemoOnlyTestFetch , timeLimitsLeiosFetch , codecLeiosFetch , codecLeiosFetchId + , leiosFetchMiniProtocolNum ) where import qualified Codec.CBOR.Decoding as CBOR @@ -30,6 +31,7 @@ import Data.ByteString.Lazy (ByteString) import Data.Kind (Type) import Data.Singletons import Data.Word (Word16, Word64) +import qualified Network.Mux.Types as Mux import Network.TypedProtocol.Codec.CBOR import Network.TypedProtocol.Core import Ouroboros.Network.Protocol.Limits @@ -38,6 +40,9 @@ import Text.Printf ----- +leiosFetchMiniProtocolNum :: Mux.MiniProtocolNum +leiosFetchMiniProtocolNum = Mux.MiniProtocolNum 19 + type LeiosFetch :: Type -> Type -> Type -> Type data LeiosFetch point eb tx where StIdle :: LeiosFetch point eb tx diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index bd90abc83f..4339f7b1b1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -19,6 +19,7 @@ module LeiosDemoOnlyTestNotify , timeLimitsLeiosNotify , codecLeiosNotify , codecLeiosNotifyId + , leiosNotifyMiniProtocolNum ) where import qualified Codec.CBOR.Decoding as CBOR @@ -29,6 +30,7 @@ import Control.Monad.Class.MonadST import Data.ByteString.Lazy (ByteString) import Data.Kind (Type) import Data.Singletons +import qualified Network.Mux.Types as Mux import Network.TypedProtocol.Codec.CBOR import Network.TypedProtocol.Core import Ouroboros.Network.Protocol.Limits @@ -37,6 +39,9 @@ import Text.Printf ----- +leiosNotifyMiniProtocolNum :: Mux.MiniProtocolNum +leiosNotifyMiniProtocolNum = Mux.MiniProtocolNum 18 + type LeiosNotify :: Type -> Type -> Type data LeiosNotify point announcement where StIdle :: LeiosNotify point announcement From 8ecc04bb45b39fcdfeb763088957503982006825 Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Fri, 24 Oct 2025 17:37:04 +0200 Subject: [PATCH 057/119] Delay throwing ReachedImmutableTip to allow clients to fetch blocks --- .../Cardano/Tools/ImmDBServer/MiniProtocols.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 9f8a2178fe..3980c1cf4c 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -201,6 +201,7 @@ chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ d ImmutableDB.iteratorNext iterator >>= \case ImmutableDB.IteratorExhausted -> do ImmutableDB.iteratorClose iterator + threadDelay 10 throwIO ReachedImmutableTip ImmutableDB.IteratorResult a -> do -- Wait until the slot of the current block has been reached From 5976d2d16ebdf0dd216a0879f600054273adb22f Mon Sep 17 00:00:00 2001 From: Drazen Popovic Date: Fri, 24 Oct 2025 17:50:27 +0200 Subject: [PATCH 058/119] Adds journal logs from leios-node and adjust up the Python scripts --- nix/leios-mvd/immdb-node/os.nix | 1 + nix/leios-mvd/test.nix | 2 + .../leios-demo/data/cardano-node.logs.json | 1387 +++++++++++++++++ scripts/leios-demo/demo_analysis.ipynb | 95 +- scripts/leios-demo/jupyter_utils.py | 119 ++ 5 files changed, 1534 insertions(+), 70 deletions(-) create mode 100644 scripts/leios-demo/data/cardano-node.logs.json create mode 100644 scripts/leios-demo/jupyter_utils.py diff --git a/nix/leios-mvd/immdb-node/os.nix b/nix/leios-mvd/immdb-node/os.nix index 8b225d23fa..cbec8e7861 100644 --- a/nix/leios-mvd/immdb-node/os.nix +++ b/nix/leios-mvd/immdb-node/os.nix @@ -4,4 +4,5 @@ ]; cardano.immdb-server.enable = true; + cardano.immdb-server.initialSlot = 500; } diff --git a/nix/leios-mvd/test.nix b/nix/leios-mvd/test.nix index 169cd6a570..e4ac28f855 100644 --- a/nix/leios-mvd/test.nix +++ b/nix/leios-mvd/test.nix @@ -35,6 +35,8 @@ # Collect logs from leios-node (read them in result/cardano.logs) leios_node.execute("journalctl -u cardano-node --no-pager > cardano-node.logs") + leios_node.execute("journalctl -u cardano-node --output json > cardano-node.logs.json") leios_node.copy_from_vm("cardano-node.logs", "") + leios_node.copy_from_vm("cardano-node.logs.json", "") ''; } diff --git a/scripts/leios-demo/data/cardano-node.logs.json b/scripts/leios-demo/data/cardano-node.logs.json new file mode 100644 index 0000000000..7f28482450 --- /dev/null +++ b/scripts/leios-demo/data/cardano-node.logs.json @@ -0,0 +1,1387 @@ +{"_GID":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SOURCE_REALTIME_TIMESTAMP":"1761317013770662","CODE_FILE":"src/core/job.c","_EXE":"/nix/store/cym39cl4v79bmbng4bvafkxagz96f4hw-systemd-255.6/lib/systemd/systemd","JOB_ID":"86","INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"Started cardano-node node 0 service.","CODE_FUNC":"job_emit_done_message","_SYSTEMD_UNIT":"init.scope","_CAP_EFFECTIVE":"1ffffffffff","_HOSTNAME":"leios-node","__SEQNUM":"1282","CODE_LINE":"796","JOB_RESULT":"done","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"systemd","PRIORITY":"6","_SYSTEMD_SLICE":"-.slice","__REALTIME_TIMESTAMP":"1761317013770703","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/init.scope","MESSAGE_ID":"39f53479d3a045ac8e11786248231fbf","SYSLOG_FACILITY":"3","TID":"1","JOB_TYPE":"start","UNIT":"cardano-node.service","_TRANSPORT":"journal","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=502;b=082ebd52b7694299b9566558b64d809c;m=138b60e;t=641e892f151cf;x=b2a8aa36f35713ce","_PID":"1","_SELINUX_CONTEXT":"kernel","_CMDLINE":"/run/current-system/systemd/lib/systemd/systemd","_UID":"0","_COMM":"systemd","__MONOTONIC_TIMESTAMP":"20493838"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317014159125","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"20882258","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=509;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=b5e9d36b2858aa02","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1289","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_GID":"10016","_COMM":"cardano-node-st","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"Starting: exec /nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"MESSAGE":"--config /etc/cardano-node/config.json","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50a;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=28655effba7def78","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node-st","_HOSTNAME":"leios-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317014159125","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__MONOTONIC_TIMESTAMP":"20882258","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1290","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_UID":"10016","_COMM":"cardano-node-st","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_FACILITY":"3","__SEQNUM":"1291","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","__REALTIME_TIMESTAMP":"1761317014159125","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50b;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=3a0afa2b659f3112","MESSAGE":"--database-path /var/lib/cardano-node/db-preview","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"20882258"} +{"_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM":"1292","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317014159125","__MONOTONIC_TIMESTAMP":"20882258","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50c;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=9dc3cb463bb97bdd","_COMM":"cardano-node-st","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","MESSAGE":"--topology /etc/cardano-node/topology.json","_HOSTNAME":"leios-node"} +{"_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317014159125","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_GID":"10016","_SYSTEMD_SLICE":"system.slice","MESSAGE":"--host-addr 0.0.0.0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50d;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=de8c657ea0cde49d","__MONOTONIC_TIMESTAMP":"20882258","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node-st","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_UID":"10016","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1293","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM":"1294","__MONOTONIC_TIMESTAMP":"20882258","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317014159125","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50e;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=b9fcdd2db3870f94","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","MESSAGE":"--port 3001","_GID":"10016","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node-st","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"PRIORITY":"6","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1295","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"20882258","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node-st","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__REALTIME_TIMESTAMP":"1761317014159125","MESSAGE":"--socket-path /run/cardano-node/node.socket","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=50f;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=17e564815ff06da6"} +{"__REALTIME_TIMESTAMP":"1761317014159125","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"20882258","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_UID":"10016","MESSAGE":"--signing-key /etc/cardano-node/byron-delegate.key","_COMM":"cardano-node-st","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=510;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=dd4dee09bf37d210","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","PRIORITY":"6","__SEQNUM":"1296","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice"} +{"__SEQNUM":"1297","__MONOTONIC_TIMESTAMP":"20882258","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"--delegation-certificate /etc/cardano-node/byron-delegation.cert","_COMM":"cardano-node-st","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317014159125","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=511;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=4e87f96bec17a3f1","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_PID":"759","_CAP_EFFECTIVE":"0"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=512;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=221effb919487fa8","_COMM":"cardano-node-st","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__MONOTONIC_TIMESTAMP":"20882258","__REALTIME_TIMESTAMP":"1761317014159125","__SEQNUM":"1298","_GID":"10016","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","MESSAGE":"--shelley-vrf-key /etc/cardano-node/vrf.skey","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"20882258","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node-st","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=513;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=68e9b42835e0ded","_PID":"759","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317014159125","MESSAGE":"--shelley-kes-key /etc/cardano-node/kes.skey","__SEQNUM":"1299","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice"} +{"MESSAGE":"--shelley-operational-certificate /etc/cardano-node/opcert.cert","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__SEQNUM":"1300","_COMM":"cardano-node-st","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"20882258","_GID":"10016","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=514;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=9c7f0f52cd2cdb3d","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__REALTIME_TIMESTAMP":"1761317014159125"} +{"_PID":"759","_COMM":"cardano-node-st","__SEQNUM":"1301","PRIORITY":"6","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=515;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=99193e6cd63193e6","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","MESSAGE":"+RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"20882258","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317014159125"} +{"_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=516;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=318c9a721b4e4520","PRIORITY":"6","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node-st","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__SEQNUM":"1302","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"-N2","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","__REALTIME_TIMESTAMP":"1761317014159125","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"20882258","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_COMM":"cardano-node-st","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"20882258","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1303","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317014159125","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=517;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=ce24f28a726fc75a","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","MESSAGE":"-I0","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","__MONOTONIC_TIMESTAMP":"20882258","__REALTIME_TIMESTAMP":"1761317014159125","_GID":"10016","MESSAGE":"-A16m","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_COMM":"cardano-node-st","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1304","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=518;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=b54389e778784f6c","PRIORITY":"6","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3"} +{"__SEQNUM":"1305","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_GID":"10016","MESSAGE":"-qg","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=519;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=eaf3427116995b4b","__REALTIME_TIMESTAMP":"1761317014159125","_UID":"10016","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"20882258","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node-st","_CAP_EFFECTIVE":"0"} +{"__MONOTONIC_TIMESTAMP":"20882258","_COMM":"cardano-node-st","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1306","MESSAGE":"-qb","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317014159125","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=51a;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=bcdd2d710a253a7f"} +{"_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_COMM":"cardano-node-st","_PID":"759","_UID":"10016","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"20882258","MESSAGE":"--disable-delayed-os-memory-return","_TRANSPORT":"stdout","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=51b;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=9595cd2833c03e84","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM":"1307","__REALTIME_TIMESTAMP":"1761317014159125"} +{"__REALTIME_TIMESTAMP":"1761317014159125","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","__MONOTONIC_TIMESTAMP":"20882258","SYSLOG_FACILITY":"3","__SEQNUM":"1308","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=51c;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=abb4b8c074df3a5f","_COMM":"cardano-node-st","_HOSTNAME":"leios-node","_UID":"10016","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","MESSAGE":"-RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=51d;b=082ebd52b7694299b9566558b64d809c;m=13ea352;t=641e892f73f15;x=8d1fc5a48f01788","MESSAGE":"..or, once again, in a single line:","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","__SEQNUM":"1309","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","PRIORITY":"6","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317014159125","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"20882258","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_COMM":"cardano-node-st","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"21020440","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"exec /nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=51e;b=082ebd52b7694299b9566558b64d809c;m=140bf18;t=641e892f95ac0;x=228abc5dc5fc287e","SYSLOG_FACILITY":"3","__SEQNUM":"1310","_COMM":"cardano-node-st","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash /nix/store/hwnb0r0pz75ipn0m8zhmq1jx4j8ngy6i-unit-script-cardano-node-start/bin/cardano-node-start","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317014297280","_EXE":"/nix/store/agkxax48k35wdmkhmmija2i2sxg8i7ny-bash-5.2p26/bin/bash","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=520;b=082ebd52b7694299b9566558b64d809c;m=15a495c;t=641e89312e524;x=7740fe70196f43e2","__MONOTONIC_TIMESTAMP":"22694236","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317015971108","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1312","_COMM":"cardano-node","MESSAGE":null,"SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_PID":"759","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:35.942471596Z\",\"ns\":\"Reflection.TracerInfo\",\"data\":{\"allTracers\":\" BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockFetch.Server BlockchainTime ChainDB ChainDB.ReplayBlock ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised ChainSync.ServerBlock ChainSync.ServerHeader Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup Forge.Loop Forge.StateInfo Forge.Stats KeepAlive.Remote Mempool Net Net.Churn Net.ConnectionManager.Local Net.ConnectionManager.Remote Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Local Net.InboundGovernor.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.PeerSelection.Selection Net.Peers.Ledger Net.Peers.List Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxInbound TxSubmission.TxOutbound Version\",\"kind\":\"TracerMeta\",\"noMetrics\":\"BlockFetch.Client BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised BlockchainTime ChainSync.Client ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Consensus.GSM Consensus.SanityCheck Consensus.Startup KeepAlive.Remote Net Net.ConnectionManager.Transition Net.Handshake.Local Net.Handshake.Remote Net.InboundGovernor.Transition Net.Mux.Local Net.Mux.Remote Net.PeerSelection.Actions Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.Ledger Net.Peers.LocalRoot Net.Peers.PublicRoot Net.Server.Local Net.Server.Remote NodeState PeerSharing.Remote Shutdown Startup.DiffusionInit StateQueryServer TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound\",\"silentTracers\":\"BlockFetch.Decision BlockFetch.Remote BlockFetch.Remote.Serialised ChainDB.ReplayBlock ChainSync.Local ChainSync.Remote ChainSync.Remote.Serialised ChainSync.ServerBlock Consensus.CSJ Consensus.DevotedBlockFetch Consensus.GDD Forge.Stats KeepAlive.Remote Net Net.Churn Net.ConnectionManager.Transition Net.PeerSelection.Initiator Net.PeerSelection.Responder Net.Peers.List PeerSharing.Remote TxSubmission.Local TxSubmission.LocalServer TxSubmission.MonitorClient TxSubmission.Remote TxSubmission.TxOutbound\"},\"sev\":\"Notice\",\"thread\":\"5\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_PID":"759","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=521;b=082ebd52b7694299b9566558b64d809c;m=15c3b70;t=641e89314d736;x=b6e5f9427dc49123","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317016098614","__MONOTONIC_TIMESTAMP":"22821744","_COMM":"cardano-node","__SEQNUM":"1313","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1314","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"22878084","SYSLOG_FACILITY":"3","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=522;b=082ebd52b7694299b9566558b64d809c;m=15d1784;t=641e89315b34a;x=6b6aeac259c4a9a7","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","MESSAGE":null,"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317016154954","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_UID":"10016"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:35.967723409Z\",\"ns\":\"Version.NodeVersion\",\"data\":{\"applicationName\":\"cardano-node\",\"applicationVersion\":\"10.5.1\",\"architecture\":\"x86_64\",\"compilerName\":\"ghc\",\"compilerVersion\":\"9.6.5\",\"gitRevision\":\"ca1ec278070baf4481564a6ba7b4a5b9e3d9f366\",\"osName\":\"linux\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__SEQNUM":"1315","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=523;b=082ebd52b7694299b9566558b64d809c;m=15e5535;t=641e89316f0eb;x=2537d2e0827eba19","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"22959413","__REALTIME_TIMESTAMP":"1761317016236267","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1316","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.150494683Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":117065736,\"CentiBlkIO\":0,\"CentiCpu\":53,\"CentiGC\":0,\"CentiMut\":47,\"FsRd\":48230400,\"FsWr\":0,\"GcsMajor\":1,\"GcsMinor\":3,\"Heap\":39845888,\"Live\":2227368,\"NetRd\":0,\"NetWr\":0,\"RSS\":81657856,\"Threads\":9,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=524;b=082ebd52b7694299b9566558b64d809c;m=15e5535;t=641e89316f0eb;x=9db8cb46b19b1f55","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016236267","_GID":"10016","__MONOTONIC_TIMESTAMP":"22959413","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.153176029Z\",\"ns\":\"Startup.MovedTopLevelOption\",\"data\":{\"kind\":\"MovedTopLevelOption\",\"option\":\"SnapshotInterval\"},\"sev\":\"Warning\",\"thread\":\"5\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317016253277","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"22976406","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=525;b=082ebd52b7694299b9566558b64d809c;m=15e9796;t=641e89317335d;x=375c255997c6a7ea","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM":"1317","_PID":"759","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"22989070","_PID":"759","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.265239993Z\",\"ns\":\"ChainDB.LastShutdownUnclean\",\"data\":{\"kind\":\"LastShutdownUnclean\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_UID":"10016","__SEQNUM":"1318","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317016265861","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=526;b=082ebd52b7694299b9566558b64d809c;m=15ec90e;t=641e893176485;x=9aff0364d11fa2d9","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=527;b=082ebd52b7694299b9566558b64d809c;m=15ee2cb;t=641e893177e90;x=6b7e56eaa3ee474c","_PID":"759","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317016272528","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1319","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"22995659","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.271420387Z\",\"ns\":\"ChainDB.OpenEvent.StartedOpeningDB\",\"data\":{\"kind\":\"StartedOpeningDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=528;b=082ebd52b7694299b9566558b64d809c;m=15ef5cc;t=641e893179191;x=500acd8c6fe231a0","__SEQNUM":"1320","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23000524","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317016277393","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.271491066Z\",\"ns\":\"ChainDB.OpenEvent.StartedOpeningImmutableDB\",\"data\":{\"kind\":\"StartedOpeningImmutableDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","PRIORITY":"6","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=529;b=082ebd52b7694299b9566558b64d809c;m=15f0882;t=641e89317a447;x=255ba5f2e0f72d2d","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1321","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317016282183","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23005314","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.28163202Z\",\"ns\":\"ChainDB.ImmDbEvent.NoValidLastLocation\",\"data\":{\"kind\":\"NoValidLastLocation\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM":"1322","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52a;b=082ebd52b7694299b9566558b64d809c;m=15f1bd3;t=641e89317b798;x=e5f08220ec605433","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317016287128","_RUNTIME_SCOPE":"system","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23010259","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.286717024Z\",\"ns\":\"ChainDB.OpenEvent.OpenedImmutableDB\",\"data\":{\"epoch\":\"0\",\"immtip\":{\"kind\":\"GenesisPoint\"},\"kind\":\"OpenedImmutableDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317016294538","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"23017672","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1323","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.291141329Z\",\"ns\":\"ChainDB.OpenEvent.StartedOpeningVolatileDB\",\"data\":{\"kind\":\"StartedOpeningVolatileDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52b;b=082ebd52b7694299b9566558b64d809c;m=15f38c8;t=641e89317d48a;x=616f2a69120903e"} +{"__SEQNUM":"1324","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.300601191Z\",\"ns\":\"ChainDB.OpenEvent.OpenedVolatileDB\",\"data\":{\"kind\":\"OpenedVolatileDB\",\"maxSlotNo\":\"NoMaxSlotNo\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52c;b=082ebd52b7694299b9566558b64d809c;m=15f52b3;t=641e89317ee76;x=48af100ff8db8507","_PID":"759","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"23024307","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317016301174","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM":"1325","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__REALTIME_TIMESTAMP":"1761317016306673","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52d;b=082ebd52b7694299b9566558b64d809c;m=15f6829;t=641e8931803f1;x=5c62638483176646","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"23029801","PRIORITY":"6","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.301297369Z\",\"ns\":\"ChainDB.OpenEvent.StartedOpeningLgrDB\",\"data\":{\"kind\":\"StartedOpeningLgrDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node"} +{"PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23033891","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_GID":"10016","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317016310763","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__SEQNUM":"1326","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.306300798Z\",\"ns\":\"ChainDB.LedgerEvent.Replay.ReplayStart.ReplayFromGenesis\",\"data\":{\"kind\":\"ReplayFromGenesis\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52e;b=082ebd52b7694299b9566558b64d809c;m=15f7823;t=641e8931813eb;x=3498df96b5d92bde"} +{"_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=52f;b=082ebd52b7694299b9566558b64d809c;m=15fa13f;t=641e893183d03;x=7e3875b0985ad654","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23044415","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317016321283","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1327","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.321012165Z\",\"ns\":\"ChainDB.OpenEvent.OpenedLgrDB\",\"data\":{\"kind\":\"OpenedLgrDB\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_COMM":"cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016325690","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=530;b=082ebd52b7694299b9566558b64d809c;m=15fb274;t=641e893184e3a;x=c4a6ef61c1a4ae07","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23048820","_RUNTIME_SCOPE":"system","_PID":"759","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.325006807Z\",\"ns\":\"ChainDB.InitChainSelEvent.StartedInitChainSelection\",\"data\":{\"kind\":\"Follower.StartedInitChainSelection\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__SEQNUM":"1328","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=531;b=082ebd52b7694299b9566558b64d809c;m=15fccdc;t=641e89318689e;x=df92b22b93a7b4a4","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.332096814Z\",\"ns\":\"ChainDB.InitChainSelEvent.InitialChainSelected\",\"data\":{\"kind\":\"Follower.InitialChainSelected\"},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"23055580","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__REALTIME_TIMESTAMP":"1761317016332446","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1329","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout"} +{"__SEQNUM":"1330","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317016340393","_SYSTEMD_SLICE":"system.slice","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.339423164Z\",\"ns\":\"ChainDB.OpenEvent.OpenedDB\",\"data\":{\"immtip\":{\"kind\":\"GenesisPoint\"},\"kind\":\"OpenedDB\",\"tip\":{\"kind\":\"GenesisPoint\"}},\"sev\":\"Info\",\"thread\":\"5\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=532;b=082ebd52b7694299b9566558b64d809c;m=15febe7;t=641e8931887a9;x=91f0452078675e79","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23063527","_HOSTNAME":"leios-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"23063527","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"1331","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=533;b=082ebd52b7694299b9566558b64d809c;m=15febe7;t=641e8931887a9;x=552ee24a55e60853","__REALTIME_TIMESTAMP":"1761317016340393","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.34009811Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.352989413Z\",\"ns\":\"BlockchainTime.CurrentSlotUnknown\",\"data\":{\"kind\":\"CurrentSlotUnknown\",\"time\":\"2025-10-24 14:43:36.35179848 UTC\"},\"sev\":\"Warning\",\"thread\":\"5\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"23076633","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=534;b=082ebd52b7694299b9566558b64d809c;m=1601f19;t=641e89318bad5;x=ff621fbf41467703","_PID":"759","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_HOSTNAME":"leios-node","PRIORITY":"6","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016353493","__SEQNUM":"1332","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.362823903Z\",\"ns\":\"Shutdown.ArmedAt\",\"data\":{\"kind\":\"ShutdownArmedAt\",\"limit\":{\"tag\":\"NoShutdown\"}},\"sev\":\"Warning\",\"thread\":\"5\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=535;b=082ebd52b7694299b9566558b64d809c;m=16045a6;t=641e89318e16a;x=43c9bdc5e340da4","__SEQNUM":"1333","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23086502","__REALTIME_TIMESTAMP":"1761317016363370","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_COMM":"cardano-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.36862492Z\",\"ns\":\"Startup.DiffusionInit.CreateSystemdSocketForSnocketPath\",\"data\":{\"kind\":\"CreateSystemdSocketForSnocketPath\",\"path\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317016370738","__MONOTONIC_TIMESTAMP":"23093872","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1334","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=536;b=082ebd52b7694299b9566558b64d809c;m=1606270;t=641e89318fe32;x=a8791336042f71b2","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016"} +{"PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016378955","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"23102084","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM":"1335","_GID":"10016","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.368689733Z\",\"ns\":\"Startup.DiffusionInit.CreatedLocalSocket\",\"data\":{\"kind\":\"CreatedLocalSocket\",\"path\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=537;b=082ebd52b7694299b9566558b64d809c;m=1608284;t=641e893191e4b;x=ca760c316ee4cee9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317016378955","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=538;b=082ebd52b7694299b9566558b64d809c;m=1608284;t=641e893191e4b;x=c463c5c796d91b3c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"23102084","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1336","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.368717669Z\",\"ns\":\"Startup.DiffusionInit.ConfiguringLocalSocket\",\"data\":{\"kind\":\"ConfiguringLocalSocket\",\"path\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\",\"socket\":\"FileDescriptor 20\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}"} +{"_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1337","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016378955","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"23102084","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=539;b=082ebd52b7694299b9566558b64d809c;m=1608284;t=641e893191e4b;x=d6b3e9b2b7d9b763","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.368780526Z\",\"ns\":\"Startup.DiffusionInit.ListeningLocalSocket\",\"data\":{\"kind\":\"ListeningLocalSocket\",\"path\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\",\"socket\":\"FileDescriptor 20\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}"} +{"_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.368813491Z\",\"ns\":\"Startup.DiffusionInit.LocalSocketUp\",\"data\":{\"kind\":\"LocalSocketUp\",\"path\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\",\"socket\":\"FileDescriptor 20\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_GID":"10016","__SEQNUM":"1338","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23102084","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317016378955","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53a;b=082ebd52b7694299b9566558b64d809c;m=1608284;t=641e893191e4b;x=5126cd2d205dcdd5","_UID":"10016"} +{"_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.369472793Z\",\"ns\":\"Startup.DiffusionInit.RunLocalServer\",\"data\":{\"kind\":\"RunLocalServer\",\"localAddress\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\"\"},\"sev\":\"Info\",\"thread\":\"41\",\"host\":\"leios-node\"}","__SEQNUM":"1339","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23126093","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317016402961","_RUNTIME_SCOPE":"system","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53b;b=082ebd52b7694299b9566558b64d809c;m=160e04d;t=641e893197c11;x=b5e17b2f8d4a7f99"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.369516095Z\",\"ns\":\"Net.Server.Local.Started\",\"data\":{\"addresses\":[{\"path\":\"/run/cardano-node/node.socket\"}],\"kind\":\"AcceptPolicyTrace\"},\"sev\":\"Notice\",\"thread\":\"41\",\"host\":\"leios-node\"}","__SEQNUM":"1340","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317016412348","PRIORITY":"6","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53c;b=082ebd52b7694299b9566558b64d809c;m=16104f7;t=641e89319a0bc;x=2137787a91a743ff","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__MONOTONIC_TIMESTAMP":"23135479","_PID":"759","SYSLOG_FACILITY":"3"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317016412348","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.369842393Z\",\"ns\":\"Startup.DiffusionInit.CreatingServerSocket\",\"data\":{\"kind\":\"CreatingServerSocket\",\"socket\":\"0.0.0.0:3001\"},\"sev\":\"Info\",\"thread\":\"40\",\"host\":\"leios-node\"}","PRIORITY":"6","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1341","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"23135479","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53d;b=082ebd52b7694299b9566558b64d809c;m=16104f7;t=641e89319a0bc;x=33f38ec4fd1e06f8","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_GID":"10016","_CAP_EFFECTIVE":"0"} +{"_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53e;b=082ebd52b7694299b9566558b64d809c;m=16104f7;t=641e89319a0bc;x=879f6582cab81eae","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.370089352Z\",\"ns\":\"Startup.DiffusionInit.ConfiguringServerSocket\",\"data\":{\"kind\":\"ConfiguringServerSocket\",\"socket\":\"0.0.0.0:3001\"},\"sev\":\"Info\",\"thread\":\"40\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317016412348","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"23135479","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1342","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__SEQNUM":"1343","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317016412348","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=53f;b=082ebd52b7694299b9566558b64d809c;m=16104f7;t=641e89319a0bc;x=f1ae67edb09f8165","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23135479","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.370270101Z\",\"ns\":\"Startup.DiffusionInit.ListeningServerSocket\",\"data\":{\"kind\":\"ListeningServerSocket\",\"socket\":\"0.0.0.0:3001\"},\"sev\":\"Info\",\"thread\":\"40\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_COMM":"cardano-node"} +{"__MONOTONIC_TIMESTAMP":"23154110","__SEQNUM":"1344","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=540;b=082ebd52b7694299b9566558b64d809c;m=1614dbe;t=641e89319e979;x=3e62d7db6ead1b9b","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.370339942Z\",\"ns\":\"Startup.DiffusionInit.ServerSocketUp\",\"data\":{\"kind\":\"ServerSocketUp\",\"socket\":\"0.0.0.0:3001\"},\"sev\":\"Info\",\"thread\":\"40\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016430969"} +{"SYSLOG_FACILITY":"3","PRIORITY":"6","_PID":"759","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=541;b=082ebd52b7694299b9566558b64d809c;m=16167f3;t=641e8931a03b4;x=30fa79e91fc7e707","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317016437684","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1345","_GID":"10016","__MONOTONIC_TIMESTAMP":"23160819","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.370406431Z\",\"ns\":\"Net.Server.Remote.Started\",\"data\":{\"addresses\":[{\"addr\":\"0.0.0.0\",\"port\":\"3001\"}],\"kind\":\"AcceptPolicyTrace\"},\"sev\":\"Notice\",\"thread\":\"40\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:36.378069137Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootDomains\",\"data\":{\"kind\":\"LocalRootDomains\",\"localRootDomains\":[[1,1,[[{\"address\":\"immdb-node.local\",\"port\":3001},{\"diffusionMode\":\"InitiatorAndResponderDiffusionMode\",\"extraFlags\":\"IsTrustable\",\"peerAdvertise\":false}]]]]},\"sev\":\"Info\",\"thread\":\"50\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=542;b=082ebd52b7694299b9566558b64d809c;m=1618af3;t=641e8931a26b5;x=34d6a5afc0ebeb27","__MONOTONIC_TIMESTAMP":"23169779","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317016446645","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1346","SYSLOG_FACILITY":"3","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout"} +{"__SEQNUM":"1347","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.378134788Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootDNSMap\",\"data\":{\"dnsMap\":{\"immdb-node.local:3001\":[]},\"kind\":\"TraceLocalRootDNSMap\"},\"sev\":\"Info\",\"thread\":\"50\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317016455513","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"23178656","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=543;b=082ebd52b7694299b9566558b64d809c;m=161ada0;t=641e8931a4959;x=1ce2897cb114bd98"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.396398841Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=544;b=082ebd52b7694299b9566558b64d809c;m=161ca8b;t=641e8931a6618;x=8769f5639b0d2e85","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317016462872","PRIORITY":"6","_GID":"10016","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM":"1348","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__MONOTONIC_TIMESTAMP":"23186059"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23186059","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1349","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=545;b=082ebd52b7694299b9566558b64d809c;m=161ca8b;t=641e8931a6618;x=7ebe0da79dcc0adc","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.43645924Z\",\"ns\":\"Startup.DiffusionInit.RunServer\",\"data\":{\"kind\":\"RunServer\",\"socketAddress\":\"0.0.0.0:3001 :| []\"},\"sev\":\"Info\",\"thread\":\"47\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317016462872","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__SEQNUM":"1350","_COMM":"cardano-node","PRIORITY":"6","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=546;b=082ebd52b7694299b9566558b64d809c;m=161eef6;t=641e8931a8ab0;x=5a8dd74d506fb50b","_GID":"10016","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317016472240","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23195382","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.443056447Z\",\"ns\":\"Net.PeerSelection.Selection.TargetsChanged\",\"data\":{\"current\":{\"kind\":\"PeerSelectionTargets\",\"targetActiveBigLedgerPeers\":5,\"targetActivePeers\":15,\"targetEstablishedBigLedgerPeers\":10,\"targetEstablishedPeers\":40,\"targetKnownBigLedgerPeers\":15,\"targetKnownPeers\":150,\"targetRootPeers\":0},\"kind\":\"TargetsChanged\",\"previous\":{\"kind\":\"PeerSelectionTargets\",\"targetActiveBigLedgerPeers\":0,\"targetActivePeers\":0,\"targetEstablishedBigLedgerPeers\":0,\"targetEstablishedPeers\":0,\"targetKnownBigLedgerPeers\":0,\"targetKnownPeers\":0,\"targetRootPeers\":0}},\"sev\":\"Notice\",\"thread\":\"54\",\"host\":\"leios-node\"}"} +{"_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.443243622Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersRequest\",\"data\":{\"kind\":\"BigLedgerPeersRequest\",\"numberOfBigLedgerPeers\":0,\"targetNumberOfBigLedgerPeers\":15},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"23208537","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317016485408","__SEQNUM":"1351","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=547;b=082ebd52b7694299b9566558b64d809c;m=1622259;t=641e8931abe20;x=addb2f219581b1bf"} +{"_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"23208537","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1352","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=548;b=082ebd52b7694299b9566558b64d809c;m=1622259;t=641e8931abe20;x=85dde5ec8c19c203","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016485408","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_COMM":"cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.443997628Z\",\"ns\":\"Consensus.GSM.GsmEventPreSyncingToSyncing\",\"data\":{\"kind\":\"GsmEventPreSyncingToSyncing\"},\"sev\":\"Info\",\"thread\":\"30\",\"host\":\"leios-node\"}","_GID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","SYSLOG_FACILITY":"3"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=549;b=082ebd52b7694299b9566558b64d809c;m=1622259;t=641e8931abe20;x=84605c0e2bde4b92","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM":"1353","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317016485408","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.44565985Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_UID":"10016","__MONOTONIC_TIMESTAMP":"23208537","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1354","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317016499382","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.445729412Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":15},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54a;b=082ebd52b7694299b9566558b64d809c;m=16258ef;t=641e8931af4b6;x=d0207eed98784d69","PRIORITY":"6","_UID":"10016","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"23222511"} +{"_PID":"759","__SEQNUM":"1355","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.446059622Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":23.168889652,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54b;b=082ebd52b7694299b9566558b64d809c;m=162739d;t=641e8931b0f64;x=64a4a144d5ab8ea1","__REALTIME_TIMESTAMP":"1761317016506212","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"23229341","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system"} +{"SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"23229341","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.446119127Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_GID":"10016","_PID":"759","__SEQNUM":"1356","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54c;b=082ebd52b7694299b9566558b64d809c;m=162739d;t=641e8931b0f64;x=e545d9aca56611f7","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016506212","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:36.446278924Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"57\",\"host\":\"leios-node\"}","__SEQNUM":"1357","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54d;b=082ebd52b7694299b9566558b64d809c;m=162739d;t=641e8931b0f64;x=d894a720b7c2b1","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"23229341","__REALTIME_TIMESTAMP":"1761317016506212","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node"} +{"_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_HOSTNAME":"leios-node","_PID":"759","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"23229341","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.453370886Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"57\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54e;b=082ebd52b7694299b9566558b64d809c;m=162739d;t=641e8931b0f64;x=dc56ad8429f6c0df","_GID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317016506212","__SEQNUM":"1358","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1359","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23229341","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.460156665Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersResults\",\"data\":{\"diffTime\":2,\"group\":1,\"kind\":\"BigLedgerPeersResults\",\"result\":[]},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317016506212","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=54f;b=082ebd52b7694299b9566558b64d809c;m=162739d;t=641e8931b0f64;x=fad30f1e1102b297","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"23255371","__REALTIME_TIMESTAMP":"1761317016532227","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461010405Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootResult\",\"data\":{\"domainAddress\":{\"address\":\"immdb-node.local\",\"port\":3001},\"kind\":\"LocalRootResult\",\"result\":[[\"192.168.1.1\",4294967295]]},\"sev\":\"Info\",\"thread\":\"53\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__SEQNUM":"1360","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=550;b=082ebd52b7694299b9566558b64d809c;m=162d94b;t=641e8931b7503;x=a433f60548a8efa5","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system"} +{"_CAP_EFFECTIVE":"0","_GID":"10016","__REALTIME_TIMESTAMP":"1761317016539980","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23263110","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=551;b=082ebd52b7694299b9566558b64d809c;m=162f786;t=641e8931b934c;x=36640295a5cd9e88","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1361","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.46106991Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootGroups\",\"data\":{\"kind\":\"LocalRootGroups\",\"localRootGroups\":[[1,1,[[{\"address\":\"192.168.1.1\",\"port\":\"3001\"},{\"diffusionMode\":\"InitiatorAndResponderDiffusionMode\",\"extraFlags\":\"IsTrustable\",\"peerAdvertise\":false}]]]]},\"sev\":\"Info\",\"thread\":\"53\",\"host\":\"leios-node\"}"} +{"_GID":"10016","__MONOTONIC_TIMESTAMP":"23271879","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_UID":"10016","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317016548742","__SEQNUM":"1362","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461105389Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootDNSMap\",\"data\":{\"dnsMap\":{\"immdb-node.local:3001\":[{\"address\":\"192.168.1.1\",\"port\":\"3001\"}]},\"kind\":\"TraceLocalRootDNSMap\"},\"sev\":\"Info\",\"thread\":\"53\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=552;b=082ebd52b7694299b9566558b64d809c;m=16319c7;t=641e8931bb586;x=57a0cb3434bc2616","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"23281108","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317016557854","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=553;b=082ebd52b7694299b9566558b64d809c;m=1633dd4;t=641e8931bd91e;x=32adf183daa6b864","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461147573Z\",\"ns\":\"Net.Peers.LocalRoot.LocalRootWaiting\",\"data\":{\"diffTime\":\"900s\",\"domainAddress\":{\"address\":\"immdb-node.local\",\"port\":3001},\"kind\":\"LocalRootWaiting\"},\"sev\":\"Info\",\"thread\":\"53\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_UID":"10016","__SEQNUM":"1363","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_PID":"759"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461279154Z\",\"ns\":\"Net.PeerSelection.Counters\",\"data\":{\"ActiveBootstrapPeersDemotions\":0,\"activeBigLedgerPeers\":0,\"activeBigLedgerPeersDemotions\":0,\"activeBootstrapPeers\":0,\"activeLocalRootPeers\":0,\"activeLocalRootPeersDemotions\":0,\"activeNonRootPeers\":0,\"activeNonRootPeersDemotions\":0,\"activePeers\":0,\"activePeersDemotions\":0,\"coldBigLedgerPeersPromotions\":0,\"coldBootstrapPeersPromotions\":0,\"coldNonRootPeersPromotions\":0,\"coldPeersPromotions\":0,\"establishedBigLedgerPeers\":0,\"establishedBootstrapPeers\":0,\"establishedLocalRootPeers\":0,\"establishedNonRootPeers\":0,\"establishedPeers\":0,\"kind\":\"PeerSelectionCounters\",\"knownBigLedgerPeers\":0,\"knownBootstrapPeers\":0,\"knownLocalRootPeers\":1,\"knownNonRootPeers\":0,\"knownPeers\":1,\"rootPeers\":1,\"warmBigLedgerPeersDemotions\":0,\"warmBigLedgerPeersPromotions\":0,\"warmBootstrapPeersDemotions\":0,\"warmBootstrapPeersPromotions\":0,\"warmLocalRootPeersPromotions\":0,\"warmNonRootPeersDemotions\":0,\"warmNonRootPeersPromotions\":0,\"warmPeersDemotions\":0,\"warmPeersPromotions\":0},\"sev\":\"Debug\",\"thread\":\"54\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=554;b=082ebd52b7694299b9566558b64d809c;m=1636804;t=641e8931c03c6;x=fc4f9a67db343014","_PID":"759","__REALTIME_TIMESTAMP":"1761317016568774","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23291908","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM":"1364"} +{"_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=555;b=082ebd52b7694299b9566558b64d809c;m=163bc60;t=641e8931c581a;x=5419f349237b010e","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1365","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317016590362","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461513262Z\",\"ns\":\"Net.PeerSelection.Selection.LocalRootPeersChanged\",\"data\":{\"current\":{\"groups\":[[1,1,[[{\"address\":\"192.168.1.1\",\"port\":\"3001\"},{\"diffusionMode\":\"InitiatorAndResponderDiffusionMode\",\"extraFlags\":\"IsTrustable\",\"peerAdvertise\":false}]]]],\"kind\":\"LocalRootPeers\"},\"kind\":\"LocalRootPeersChanged\",\"previous\":{\"groups\":[],\"kind\":\"LocalRootPeers\"}},\"sev\":\"Notice\",\"thread\":\"54\",\"host\":\"leios-node\"}","_PID":"759","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23313504","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23313504","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=556;b=082ebd52b7694299b9566558b64d809c;m=163bc60;t=641e8931c581a;x=de3d9e95128f81dc","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461789275Z\",\"ns\":\"Net.PeerSelection.Counters\",\"data\":{\"ActiveBootstrapPeersDemotions\":0,\"activeBigLedgerPeers\":0,\"activeBigLedgerPeersDemotions\":0,\"activeBootstrapPeers\":0,\"activeLocalRootPeers\":0,\"activeLocalRootPeersDemotions\":0,\"activeNonRootPeers\":0,\"activeNonRootPeersDemotions\":0,\"activePeers\":0,\"activePeersDemotions\":0,\"coldBigLedgerPeersPromotions\":0,\"coldBootstrapPeersPromotions\":0,\"coldNonRootPeersPromotions\":0,\"coldPeersPromotions\":1,\"establishedBigLedgerPeers\":0,\"establishedBootstrapPeers\":0,\"establishedLocalRootPeers\":0,\"establishedNonRootPeers\":0,\"establishedPeers\":0,\"kind\":\"PeerSelectionCounters\",\"knownBigLedgerPeers\":0,\"knownBootstrapPeers\":0,\"knownLocalRootPeers\":1,\"knownNonRootPeers\":0,\"knownPeers\":1,\"rootPeers\":1,\"warmBigLedgerPeersDemotions\":0,\"warmBigLedgerPeersPromotions\":0,\"warmBootstrapPeersDemotions\":0,\"warmBootstrapPeersPromotions\":0,\"warmLocalRootPeersPromotions\":0,\"warmNonRootPeersDemotions\":0,\"warmNonRootPeersPromotions\":0,\"warmPeersDemotions\":0,\"warmPeersPromotions\":0},\"sev\":\"Debug\",\"thread\":\"54\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__SEQNUM":"1366","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__REALTIME_TIMESTAMP":"1761317016590362"} +{"_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_PID":"759","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=557;b=082ebd52b7694299b9566558b64d809c;m=163bc60;t=641e8931c581a;x=7b3c510740789ade","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317016590362","__SEQNUM":"1367","_COMM":"cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.461957452Z\",\"ns\":\"Net.PeerSelection.Selection.PromoteColdLocalPeers\",\"data\":{\"kind\":\"PromoteColdLocalPeers\",\"selectedPeers\":[{\"address\":\"192.168.1.1\",\"port\":\"3001\"}],\"targetLocalEstablished\":[[1,0]]},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"23313504","_GID":"10016","_CAP_EFFECTIVE":"0"} +{"_GID":"10016","__SEQNUM":"1368","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=558;b=082ebd52b7694299b9566558b64d809c;m=1645787;t=641e8931cf33e;x=a2979105c1ec566","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23353223","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.462408907Z\",\"ns\":\"Net.ConnectionManager.Remote.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Outbound\",\"remoteAddress\":{\"addr\":\"192.168.1.1\",\"port\":\"3001\"}},\"sev\":\"Debug\",\"thread\":\"58\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016630078","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system"} +{"_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.47192492Z\",\"ns\":\"Net.ConnectionManager.Remote.ConnectionNotFound\",\"data\":{\"kind\":\"ConnectionNotFound\",\"provenance\":\"Outbound\",\"remoteAddress\":{\"addr\":\"192.168.1.1\",\"port\":\"3001\"}},\"sev\":\"Debug\",\"thread\":\"58\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317016638214","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=559;b=082ebd52b7694299b9566558b64d809c;m=1647747;t=641e8931d1306;x=22ec40538c4adaf3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23361351","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__SEQNUM":"1369","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317016648467","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55a;b=082ebd52b7694299b9566558b64d809c;m=1649f4e;t=641e8931d3b13;x=43be2688f4dfc31b","SYSLOG_FACILITY":"3","__SEQNUM":"1370","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.47201767Z\",\"ns\":\"Net.ConnectionManager.Remote.Connect\",\"data\":{\"connectionId\":{\"localAddress\":{\"address\":\"0.0.0.0\",\"port\":\"3001\"},\"remoteAddress\":{\"address\":\"192.168.1.1\",\"port\":\"3001\"}},\"diffusionMode\":\"InitiatorAndResponderDiffusionMode\",\"kind\":\"Connect\"},\"sev\":\"Debug\",\"thread\":\"58\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23371598","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout"} +{"SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"23371598","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1371","_UID":"10016","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55b;b=082ebd52b7694299b9566558b64d809c;m=1649f4e;t=641e8931d3b13;x=5595cddb0084dc5b","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.504139071Z\",\"ns\":\"Net.Handshake.Remote.Send.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = 192.168.1.2:3001, remoteAddress = 192.168.1.1:3001}\",\"event\":\"Send AnyMessage MsgProposeVersions (fromList [(NodeToNodeV_14,TList [TInt 42,TBool False,TInt 0,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"59\",\"host\":\"leios-node\"}","PRIORITY":"6","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317016648467"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.515553929Z\",\"ns\":\"Net.Handshake.Remote.Receive.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = 192.168.1.2:3001, remoteAddress = 192.168.1.1:3001}\",\"event\":\"Recv AnyMessage MsgAcceptVersion NodeToNodeV_14 (TList [TInt 42,TBool True,TInt 0,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"59\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317016648467","_UID":"10016","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55c;b=082ebd52b7694299b9566558b64d809c;m=1649f4e;t=641e8931d3b13;x=5b8cc3588d55174f","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1372","PRIORITY":"6","_PID":"759","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23371598","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM":"1373","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55d;b=082ebd52b7694299b9566558b64d809c;m=1649f4e;t=641e8931d3b13;x=ab45c71a6e72104e","_UID":"10016","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.531583899Z\",\"ns\":\"Net.ConnectionManager.Remote.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"diffusionMode\":\"InitiatorOnlyDiffusionMode\",\"networkMagic\":42,\"peerSharing\":\"PeerSharingDisabled\",\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":14},\"connectionId\":{\"localAddress\":{\"address\":\"192.168.1.2\",\"port\":\"3001\"},\"remoteAddress\":{\"address\":\"192.168.1.1\",\"port\":\"3001\"}},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"59\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23371598","__REALTIME_TIMESTAMP":"1761317016648467","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.539463392Z\",\"ns\":\"Net.PeerSelection.Actions.StatusChanged\",\"data\":{\"kind\":\"PeerStatusChanged\",\"peerStatusChangeType\":\"ColdToWarm (Just 192.168.1.2:3001) 192.168.1.1:3001\"},\"sev\":\"Info\",\"thread\":\"58\",\"host\":\"leios-node\"}","_COMM":"cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM":"1374","_UID":"10016","__REALTIME_TIMESTAMP":"1761317016648467","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"23371598","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55e;b=082ebd52b7694299b9566558b64d809c;m=1649f4e;t=641e8931d3b13;x=d0edd2b3dcbdd4c7","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"23415077","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=55f;b=082ebd52b7694299b9566558b64d809c;m=1654925;t=641e8931de380;x=443d9a295c0b99e9","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.555352842Z\",\"ns\":\"Net.PeerSelection.Counters\",\"data\":{\"ActiveBootstrapPeersDemotions\":0,\"activeBigLedgerPeers\":0,\"activeBigLedgerPeersDemotions\":0,\"activeBootstrapPeers\":0,\"activeLocalRootPeers\":0,\"activeLocalRootPeersDemotions\":0,\"activeNonRootPeers\":0,\"activeNonRootPeersDemotions\":0,\"activePeers\":0,\"activePeersDemotions\":0,\"coldBigLedgerPeersPromotions\":0,\"coldBootstrapPeersPromotions\":0,\"coldNonRootPeersPromotions\":0,\"coldPeersPromotions\":0,\"establishedBigLedgerPeers\":0,\"establishedBootstrapPeers\":0,\"establishedLocalRootPeers\":1,\"establishedNonRootPeers\":0,\"establishedPeers\":1,\"kind\":\"PeerSelectionCounters\",\"knownBigLedgerPeers\":0,\"knownBootstrapPeers\":0,\"knownLocalRootPeers\":1,\"knownNonRootPeers\":0,\"knownPeers\":1,\"rootPeers\":1,\"warmBigLedgerPeersDemotions\":0,\"warmBigLedgerPeersPromotions\":0,\"warmBootstrapPeersDemotions\":0,\"warmBootstrapPeersPromotions\":0,\"warmLocalRootPeersPromotions\":0,\"warmNonRootPeersDemotions\":0,\"warmNonRootPeersPromotions\":0,\"warmPeersDemotions\":0,\"warmPeersPromotions\":0},\"sev\":\"Debug\",\"thread\":\"54\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016691584","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","PRIORITY":"6","__SEQNUM":"1375","_RUNTIME_SCOPE":"system"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=560;b=082ebd52b7694299b9566558b64d809c;m=165a959;t=641e8931e4515;x=1057ab3d7a501f92","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016716565","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.555528283Z\",\"ns\":\"Net.PeerSelection.Selection.PromoteColdDone\",\"data\":{\"actualEstablished\":1,\"kind\":\"PromoteColdDone\",\"peer\":{\"address\":\"192.168.1.1\",\"port\":\"3001\"},\"targetEstablished\":40},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM":"1376","__MONOTONIC_TIMESTAMP":"23439705","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317016716565","_COMM":"cardano-node","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1377","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.55737349Z\",\"ns\":\"Net.PeerSelection.Counters\",\"data\":{\"ActiveBootstrapPeersDemotions\":0,\"activeBigLedgerPeers\":0,\"activeBigLedgerPeersDemotions\":0,\"activeBootstrapPeers\":0,\"activeLocalRootPeers\":0,\"activeLocalRootPeersDemotions\":0,\"activeNonRootPeers\":0,\"activeNonRootPeersDemotions\":0,\"activePeers\":0,\"activePeersDemotions\":0,\"coldBigLedgerPeersPromotions\":0,\"coldBootstrapPeersPromotions\":0,\"coldNonRootPeersPromotions\":0,\"coldPeersPromotions\":0,\"establishedBigLedgerPeers\":0,\"establishedBootstrapPeers\":0,\"establishedLocalRootPeers\":1,\"establishedNonRootPeers\":0,\"establishedPeers\":1,\"kind\":\"PeerSelectionCounters\",\"knownBigLedgerPeers\":0,\"knownBootstrapPeers\":0,\"knownLocalRootPeers\":1,\"knownNonRootPeers\":0,\"knownPeers\":1,\"rootPeers\":1,\"warmBigLedgerPeersDemotions\":0,\"warmBigLedgerPeersPromotions\":0,\"warmBootstrapPeersDemotions\":0,\"warmBootstrapPeersPromotions\":0,\"warmLocalRootPeersPromotions\":1,\"warmNonRootPeersDemotions\":0,\"warmNonRootPeersPromotions\":0,\"warmPeersDemotions\":0,\"warmPeersPromotions\":1},\"sev\":\"Debug\",\"thread\":\"54\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=561;b=082ebd52b7694299b9566558b64d809c;m=165a959;t=641e8931e4515;x=a5627b604c25027","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23439705","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016"} +{"__SEQNUM":"1378","_COMM":"cardano-node","_TRANSPORT":"stdout","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=562;b=082ebd52b7694299b9566558b64d809c;m=166351a;t=641e8931ed0e1;x=15e336e107054a10","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.557550049Z\",\"ns\":\"Net.PeerSelection.Selection.PromoteWarmLocalPeers\",\"data\":{\"kind\":\"PromoteWarmLocalPeers\",\"selectedPeers\":[{\"address\":\"192.168.1.1\",\"port\":\"3001\"}],\"targetActualActive\":[[1,0]]},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"23475482","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317016752353","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.565014405Z\",\"ns\":\"Net.PeerSelection.Actions.StatusChanged\",\"data\":{\"kind\":\"PeerStatusChanged\",\"peerStatusChangeType\":\"WarmToHot (ConnectionId {localAddress = 192.168.1.2:3001, remoteAddress = 192.168.1.1:3001})\"},\"sev\":\"Info\",\"thread\":\"64\",\"host\":\"leios-node\"}","_UID":"10016","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"23482561","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__SEQNUM":"1379","__REALTIME_TIMESTAMP":"1761317016759431","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=563;b=082ebd52b7694299b9566558b64d809c;m=16650c1;t=641e8931eec87;x=e67da68794fcdc1","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node"} +{"_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.568218444Z\",\"ns\":\"Net.PeerSelection.Counters\",\"data\":{\"ActiveBootstrapPeersDemotions\":0,\"activeBigLedgerPeers\":0,\"activeBigLedgerPeersDemotions\":0,\"activeBootstrapPeers\":0,\"activeLocalRootPeers\":1,\"activeLocalRootPeersDemotions\":0,\"activeNonRootPeers\":0,\"activeNonRootPeersDemotions\":0,\"activePeers\":1,\"activePeersDemotions\":0,\"coldBigLedgerPeersPromotions\":0,\"coldBootstrapPeersPromotions\":0,\"coldNonRootPeersPromotions\":0,\"coldPeersPromotions\":0,\"establishedBigLedgerPeers\":0,\"establishedBootstrapPeers\":0,\"establishedLocalRootPeers\":1,\"establishedNonRootPeers\":0,\"establishedPeers\":1,\"kind\":\"PeerSelectionCounters\",\"knownBigLedgerPeers\":0,\"knownBootstrapPeers\":0,\"knownLocalRootPeers\":1,\"knownNonRootPeers\":0,\"knownPeers\":1,\"rootPeers\":1,\"warmBigLedgerPeersDemotions\":0,\"warmBigLedgerPeersPromotions\":0,\"warmBootstrapPeersDemotions\":0,\"warmBootstrapPeersPromotions\":0,\"warmLocalRootPeersPromotions\":0,\"warmNonRootPeersDemotions\":0,\"warmNonRootPeersPromotions\":0,\"warmPeersDemotions\":0,\"warmPeersPromotions\":0},\"sev\":\"Debug\",\"thread\":\"54\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=564;b=082ebd52b7694299b9566558b64d809c;m=16650c1;t=641e8931eec87;x=2323a5ce0e1539de","__REALTIME_TIMESTAMP":"1761317016759431","_RUNTIME_SCOPE":"system","__SEQNUM":"1380","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23482561","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice"} +{"_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1381","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.568414558Z\",\"ns\":\"Net.PeerSelection.Selection.PromoteWarmDone\",\"data\":{\"actualActive\":1,\"kind\":\"PromoteWarmDone\",\"peer\":{\"address\":\"192.168.1.1\",\"port\":\"3001\"},\"targetActive\":15},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317016784348","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23507488","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=565;b=082ebd52b7694299b9566558b64d809c;m=166b220;t=641e8931f4ddc;x=5912f9179e44027","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service"} +{"__REALTIME_TIMESTAMP":"1761317016792662","PRIORITY":"6","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=566;b=082ebd52b7694299b9566558b64d809c;m=166d292;t=641e8931f6e56;x=850dd4739b46ecc","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.714295669Z\",\"ns\":\"ChainSync.Client.FoundIntersection\",\"data\":{\"kind\":\"FoundIntersection\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1382","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"23515794","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout"} +{"_UID":"10016","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"23515794","__SEQNUM":"1383","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=567;b=082ebd52b7694299b9566558b64d809c;m=166d292;t=641e8931f6e56;x=4cab5ad0fc047c83","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317016792662","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.714690132Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759"} +{"SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.714731758Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1384","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23515794","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=568;b=082ebd52b7694299b9566558b64d809c;m=166d292;t=641e8931f6e56;x=4d4b60527c0cbab","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317016792662","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.797755438Z\",\"ns\":\"Consensus.GSM.EnterCaughtUp\",\"data\":{\"currentSelection\":{\"kind\":\"TipGenesis\"},\"kind\":\"GsmEventEnterCaughtUp\",\"peerNumber\":1},\"sev\":\"Info\",\"thread\":\"30\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_UID":"10016","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317016811243","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1385","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_PID":"759","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23534371","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=569;b=082ebd52b7694299b9566558b64d809c;m=1671b23;t=641e8931fb6eb;x=b61f5f2b234907ad","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:36.816508659Z\",\"ns\":\"ChainSync.Client.RolledBack\",\"data\":{\"kind\":\"RolledBack\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tip\":{\"kind\":\"GenesisPoint\"}},\"sev\":\"Notice\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56a;b=082ebd52b7694299b9566558b64d809c;m=1673718;t=641e8931fd2d0;x=927448b93f2758b7","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1386","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317016818384","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23541528","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317016818384","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.81655224Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56b;b=082ebd52b7694299b9566558b64d809c;m=1673718;t=641e8931fd2d0;x=4c01a930c881f88d","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23541528","SYSLOG_FACILITY":"3","__SEQNUM":"1387","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__SEQNUM":"1388","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"23541528","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317016818384","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56c;b=082ebd52b7694299b9566558b64d809c;m=1673718;t=641e8931fd2d0;x=97efbb0cda87f31a","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.816581294Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_TRANSPORT":"stdout"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56d;b=082ebd52b7694299b9566558b64d809c;m=1679035;t=641e893202bd2;x=dd6db448074e39e","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317016841170","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.838680472Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"blockNo\":0,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":2},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_PID":"759","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__MONOTONIC_TIMESTAMP":"23564341","__SEQNUM":"1389","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016"} +{"_UID":"10016","__MONOTONIC_TIMESTAMP":"23599843","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317016876709","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56e;b=082ebd52b7694299b9566558b64d809c;m=1681ae3;t=641e89320b6a5;x=4bc2c2ff18627ff9","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.855388461Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1390","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23608327","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.856337744Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":0,\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":false},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1391","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=56f;b=082ebd52b7694299b9566558b64d809c;m=1683c07;t=641e89320d7cb;x=53c357bd5d0be706","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317016885195","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=570;b=082ebd52b7694299b9566558b64d809c;m=1683c07;t=641e89320d7cb;x=2488304dadc1edf6","__MONOTONIC_TIMESTAMP":"23608327","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1392","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317016885195","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.85698615Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=571;b=082ebd52b7694299b9566558b64d809c;m=1683c07;t=641e89320d7cb;x=54bb31758b36dea6","__MONOTONIC_TIMESTAMP":"23608327","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317016885195","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.857033084Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1393","SYSLOG_FACILITY":"3","_GID":"10016"} +{"__SEQNUM":"1394","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.857101528Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"blockNo\":1,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":44},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016908953","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"23632083","PRIORITY":"6","_PID":"759","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=572;b=082ebd52b7694299b9566558b64d809c;m=16898d3;t=641e893213499;x=dd401d17386186ec","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_TRANSPORT":"stdout","__SEQNUM":"1395","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317016908953","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.861149249Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=573;b=082ebd52b7694299b9566558b64d809c;m=16898d3;t=641e893213499;x=4fd51da3bc64138","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23632083","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1396","__MONOTONIC_TIMESTAMP":"23649088","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=574;b=082ebd52b7694299b9566558b64d809c;m=168db40;t=641e893217704;x=f4af0a5de983494a","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.861267421Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":0,\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317016925956","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=575;b=082ebd52b7694299b9566558b64d809c;m=168fe57;t=641e893219a1d;x=185afdb178b6b74","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","_GID":"10016","__SEQNUM":"1397","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.861300106Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317016934941","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"23658071","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23658071","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1398","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317016934941","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=576;b=082ebd52b7694299b9566558b64d809c;m=168fe57;t=641e893219a1d;x=1493d9b7e3d8a999","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.861326646Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23658071","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=577;b=082ebd52b7694299b9566558b64d809c;m=168fe57;t=641e893219a1d;x=bd285b4f219f7c02","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.861373579Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"blockNo\":2,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":52},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317016934941","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM":"1399","_COMM":"cardano-node"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317016957589","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"23680723","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.866801085Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__SEQNUM":"1400","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=578;b=082ebd52b7694299b9566558b64d809c;m=16956d3;t=641e89321f295;x=502714ca4c8f8eb1","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=579;b=082ebd52b7694299b9566558b64d809c;m=1697780;t=641e893221346;x=8ed98533b25ebb25","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23689088","_COMM":"cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM":"1401","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016965958","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.869107803Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":1,\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.869212564Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317016972591","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57a;b=082ebd52b7694299b9566558b64d809c;m=1699166;t=641e893222d2f;x=11bf50a1edf9e59b","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23695718","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1402","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_RUNTIME_SCOPE":"system","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.86926285Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317016972591","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57b;b=082ebd52b7694299b9566558b64d809c;m=1699166;t=641e893222d2f;x=838a780042747ce","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1403","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23695718","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1404","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"23707369","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317016984242","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57c;b=082ebd52b7694299b9566558b64d809c;m=169bee9;t=641e893225ab2;x=f5506427b91134b","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.86943466Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"blockNo\":3,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":53},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317016991968","_GID":"10016","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57d;b=082ebd52b7694299b9566558b64d809c;m=169dd17;t=641e8932278e0;x=fcba8e499702aa5d","_UID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23715095","__SEQNUM":"1405","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.87651433Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice"} +{"_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1406","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23715095","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57e;b=082ebd52b7694299b9566558b64d809c;m=169dd17;t=641e8932278e0;x=ba603a5eb3260b82","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.915088786Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317016991968","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1407","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317016991968","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"23715095","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=57f;b=082ebd52b7694299b9566558b64d809c;m=169dd17;t=641e8932278e0;x=c019b09990995f6e","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_UID":"10016","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.915244113Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":2,\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23737242","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.915283224Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017014114","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"1408","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=580;b=082ebd52b7694299b9566558b64d809c;m=16a339a;t=641e89322cf62;x=37a492e4516a6e02","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317017014114","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23737242","SYSLOG_FACILITY":"3","__SEQNUM":"1409","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","PRIORITY":"6","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=581;b=082ebd52b7694299b9566558b64d809c;m=16a339a;t=641e89322cf62;x=3365433873c73278","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.915314513Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=582;b=082ebd52b7694299b9566558b64d809c;m=16a5f1f;t=641e89322fae8;x=cdfefc10f058e61f","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1410","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017025256","_RUNTIME_SCOPE":"system","PRIORITY":"6","_UID":"10016","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.915380164Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"blockNo\":4,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":59},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_PID":"759","__MONOTONIC_TIMESTAMP":"23748383","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1411","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017025256","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=583;b=082ebd52b7694299b9566558b64d809c;m=16a5f1f;t=641e89322fae8;x=bec31fb2a0970ae2","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23748383","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.925847416Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_HOSTNAME":"leios-node"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:36.934178084Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017041949","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM":"1412","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"23765078","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=584;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=c2cf71b4313b4bd8","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__MONOTONIC_TIMESTAMP":"23765078","_CAP_EFFECTIVE":"0","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.947538162Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1413","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=585;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=725117e91cc9f1c6","__REALTIME_TIMESTAMP":"1761317017041949","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=586;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=ab55282398930e1a","__REALTIME_TIMESTAMP":"1761317017041949","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.947705222Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":3,\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23765078","__SEQNUM":"1414","PRIORITY":"6","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__REALTIME_TIMESTAMP":"1761317017041949","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.947756066Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"23765078","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=587;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=ed3106e64bc7bfbe","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1415"} +{"__SEQNUM":"1416","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_UID":"10016","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317017041949","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"23765078","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=588;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=1d58f70ae92b3f38","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.947796016Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017041949","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23765078","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=589;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=512e88a85784f7ed","_PID":"759","_HOSTNAME":"leios-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1417","_GID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.964282748Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017041949","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58a;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=a6b7074600707315","_PID":"759","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1418","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.965742431Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"SendFetchRequest\",\"length\":3,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"23765078","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__REALTIME_TIMESTAMP":"1761317017041949","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1419","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23765078","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58b;b=082ebd52b7694299b9566558b64d809c;m=16aa056;t=641e893233c1d;x=f12d2ad7a1a6bf08","_PID":"759","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.965841326Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_GID":"10016"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__MONOTONIC_TIMESTAMP":"23815691","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_GID":"10016","__SEQNUM":"1420","__REALTIME_TIMESTAMP":"1761317017092564","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58c;b=082ebd52b7694299b9566558b64d809c;m=16b660b;t=641e8932401d4;x=17b7809470bf38c","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.973602368Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"SYSLOG_FACILITY":"3","__SEQNUM":"1421","PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317017092564","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23815691","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58d;b=082ebd52b7694299b9566558b64d809c;m=16b660b;t=641e8932401d4;x=3606a23cd4292dbb","MESSAGE":"{\"at\":\"2025-10-24T14:43:36.947860549Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"blockNo\":5,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":77},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_UID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1422","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"23815691","_PID":"759","__REALTIME_TIMESTAMP":"1761317017092564","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.031558896Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58e;b=082ebd52b7694299b9566558b64d809c;m=16b660b;t=641e8932401d4;x=3875e38679efe1ea","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.038358084Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"23836249","__REALTIME_TIMESTAMP":"1761317017113119","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=58f;b=082ebd52b7694299b9566558b64d809c;m=16bb659;t=641e89324521f;x=ebae8b11df018879","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_GID":"10016","_PID":"759","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1423","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=590;b=082ebd52b7694299b9566558b64d809c;m=16bb659;t=641e89324521f;x=c4923323cbc635e1","__SEQNUM":"1424","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.038525983Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":4,\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017113119","__MONOTONIC_TIMESTAMP":"23836249","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","PRIORITY":"6"} +{"_TRANSPORT":"stdout","__SEQNUM":"1425","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","PRIORITY":"6","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"23836249","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=591;b=082ebd52b7694299b9566558b64d809c;m=16bb659;t=641e89324521f;x=5557f203120d9ac1","_RUNTIME_SCOPE":"system","_GID":"10016","__REALTIME_TIMESTAMP":"1761317017113119","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.038577107Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service"} +{"_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.038617335Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1426","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317017113119","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=592;b=082ebd52b7694299b9566558b64d809c;m=16bb659;t=641e89324521f;x=220bd66f18085b9","PRIORITY":"6","_GID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23836249","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.038679354Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"blockNo\":6,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":80},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017113119","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=593;b=082ebd52b7694299b9566558b64d809c;m=16bb659;t=641e89324521f;x=6f119131f3328573","_PID":"759","__SEQNUM":"1427","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"23836249","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1428","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=594;b=082ebd52b7694299b9566558b64d809c;m=16c3773;t=641e89324d339;x=6907a97ee456a2ec","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.081287842Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_UID":"10016","__REALTIME_TIMESTAMP":"1761317017146169","_GID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"23869299","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system"} +{"__MONOTONIC_TIMESTAMP":"23875577","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1429","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.098602892Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=595;b=082ebd52b7694299b9566558b64d809c;m=16c4ff9;t=641e89324ebb8;x=2b4e3ec1a11a0d6","_HOSTNAME":"leios-node","_UID":"10016","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317017152440","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_PID":"759"} +{"__REALTIME_TIMESTAMP":"1761317017152440","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.098767997Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":5,\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=596;b=082ebd52b7694299b9566558b64d809c;m=16c4ff9;t=641e89324ebb8;x=524ae12212306435","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1430","_PID":"759","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"23875577","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1431","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"23875577","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.098817444Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317017152440","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_GID":"10016","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=597;b=082ebd52b7694299b9566558b64d809c;m=16c4ff9;t=641e89324ebb8;x=f14c4789c44d458d"} +{"_PID":"759","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.098856556Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017152440","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"23875577","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=598;b=082ebd52b7694299b9566558b64d809c;m=16c4ff9;t=641e89324ebb8;x=409675bc25a0d8c7","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1432","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node"} +{"_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=599;b=082ebd52b7694299b9566558b64d809c;m=16c4ff9;t=641e89324ebb8;x=7a5e62fb373a1a7e","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.112232278Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23875577","__SEQNUM":"1433","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_PID":"759","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317017152440","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59a;b=082ebd52b7694299b9566558b64d809c;m=16ccf75;t=641e893256b3d;x=baa353571617a745","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1434","_TRANSPORT":"stdout","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.13807858Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"23908213","_HOSTNAME":"leios-node","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317017185085","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59b;b=082ebd52b7694299b9566558b64d809c;m=16ccf75;t=641e893256b3d;x=6c2022d7a8a57996","_GID":"10016","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317017185085","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23908213","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.159849503Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"blockNo\":7,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":95},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1435"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.174242673Z\",\"ns\":\"Net.Server.Local.AcceptConnection\",\"data\":{\"address\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"AcceptConnection\"},\"sev\":\"Debug\",\"thread\":\"48\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59c;b=082ebd52b7694299b9566558b64d809c;m=16d09d0;t=641e89325a593;x=4cb5fd66a9f614ad","__MONOTONIC_TIMESTAMP":"23923152","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1436","__REALTIME_TIMESTAMP":"1761317017200019","_PID":"759","_COMM":"cardano-node","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_GID":"10016","_PID":"759","_UID":"10016","__MONOTONIC_TIMESTAMP":"23923152","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.184424414Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1437","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59d;b=082ebd52b7694299b9566558b64d809c;m=16d09d0;t=641e89325a593;x=2310bf3b3957301d","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317017200019","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__REALTIME_TIMESTAMP":"1761317017213593","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59e;b=082ebd52b7694299b9566558b64d809c;m=16d3ed1;t=641e89325da99;x=bcff2b95eb278a10","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"23936721","SYSLOG_FACILITY":"3","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:35.942471596 UTC to 2025-10-24 14:43:37.198021673 UTC","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1438","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=59f;b=082ebd52b7694299b9566558b64d809c;m=16d4c3b;t=641e89325e7f9;x=5501c14841eecc7d","__MONOTONIC_TIMESTAMP":"23940155","_GID":"10016","__SEQNUM":"1439","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017217017","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.195328034Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":117065736,\"CentiBlkIO\":0,\"CentiCpu\":64,\"CentiGC\":0,\"CentiMut\":58,\"FsRd\":50114560,\"FsWr\":8192,\"GcsMajor\":1,\"GcsMinor\":3,\"Heap\":39845888,\"Live\":2227368,\"NetRd\":0,\"NetWr\":0,\"RSS\":89784320,\"Threads\":9,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1440","_GID":"10016","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23948699","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.197619108Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317017225560","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a0;b=082ebd52b7694299b9566558b64d809c;m=16d6d9b;t=641e893260958;x=d4fcad10e5006dfa","_UID":"10016"} +{"PRIORITY":"6","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"23957794","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.198021673Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"kind\":\"AddedBlockToQueue\",\"queueSize\":1},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM":"1441","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317017234660","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a1;b=082ebd52b7694299b9566558b64d809c;m=16d9122;t=641e893262ce4;x=873b07d48ae7273e"} +{"_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.19840133Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"delay\":1364401.196465889,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":1033},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1442","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a2;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=201e705a73e98e68","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317017242955","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23966086","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_GID":"10016","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.206612988Z\",\"ns\":\"Net.ConnectionManager.Local.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Inbound\",\"remoteAddress\":{\"path\":\"/run/cardano-node/node.socket@0\"}},\"sev\":\"Debug\",\"thread\":\"75\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"23966086","__REALTIME_TIMESTAMP":"1761317017242955","_PID":"759","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a3;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=5cdd101d3aeb6e6c","__SEQNUM":"1443"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","PRIORITY":"6","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207314195Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a4;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=bde1bbfb82b368ef","__MONOTONIC_TIMESTAMP":"23966086","SYSLOG_FACILITY":"3","__SEQNUM":"1444","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017242955","_TRANSPORT":"stdout","_COMM":"cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a5;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=f9005ece34044de6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__SEQNUM":"1445","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317017242955","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"23966086","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207367274Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"kind\":\"AddedBlockToQueue\",\"queueSize\":2},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207449128Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"delay\":1364359.207132887,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a6;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=4ee672d6153b7768","_GID":"10016","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1446","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"23966086","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017242955","_COMM":"cardano-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system"} +{"_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207631274Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"Point\",\"slot\":52},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"23966086","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM":"1447","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017242955","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a7;b=082ebd52b7694299b9566558b64d809c;m=16db186;t=641e893264d4b;x=a80b1bd90cac8e4e","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_PID":"759","_TRANSPORT":"stdout"} +{"_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5a9;b=082ebd52b7694299b9566558b64d809c;m=16ea48f;t=641e893274054;x=17840804fe9f4796","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","__SEQNUM":"1449","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207717598Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"delay\":1364351.207527071,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017305172","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24028303"} +{"_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.20779582Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"24039148","__SEQNUM":"1450","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017316008","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5aa;b=082ebd52b7694299b9566558b64d809c;m=16eceec;t=641e893276aa8;x=5218e72eede99547","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__MONOTONIC_TIMESTAMP":"24039148","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.207833534Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017316008","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1451","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ab;b=082ebd52b7694299b9566558b64d809c;m=16eceec;t=641e893276aa8;x=a1533d506529e8cb"} +{"_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317017316008","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"1452","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ac;b=082ebd52b7694299b9566558b64d809c;m=16eceec;t=641e893276aa8;x=49e901b9b8654a65","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217562704Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"75\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_UID":"10016","__MONOTONIC_TIMESTAMP":"24039148","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ad;b=082ebd52b7694299b9566558b64d809c;m=16f2490;t=641e89327c057;x=1b40617b40b2b4de","_TRANSPORT":"stdout","_PID":"759","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1453","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24061072","_UID":"10016","__REALTIME_TIMESTAMP":"1761317017337943","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217604329Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"24073299","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217707415Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":6,\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5af;b=082ebd52b7694299b9566558b64d809c;m=16f5453;t=641e89327f018;x=407604c7e3b66c2a","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017350168","PRIORITY":"6","__SEQNUM":"1455"} +{"_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b0;b=082ebd52b7694299b9566558b64d809c;m=16f99d6;t=641e89328359c;x=4a37ad19e746d313","_TRANSPORT":"stdout","_UID":"10016","_GID":"10016","__SEQNUM":"1456","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317017367964","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24091094","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217742336Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217768875Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"24091094","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1457","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b1;b=082ebd52b7694299b9566558b64d809c;m=16f99d6;t=641e89328359c;x=a85bb092bfdaf9a","__REALTIME_TIMESTAMP":"1761317017367964","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b3;b=082ebd52b7694299b9566558b64d809c;m=16fd4b1;t=641e893287076;x=eb842aa416ce5917","__MONOTONIC_TIMESTAMP":"24106161","__SEQNUM":"1459","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317017383030","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.217812177Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"blockNo\":8,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":108},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_UID":"10016","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM":"1460","_UID":"10016","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017392963","PRIORITY":"6","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.225736368Z\",\"ns\":\"ChainDB.ChainSelStarvationEvent\",\"data\":{\"fallingEdge\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"kind\":\"ChainSelStarvation\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b4;b=082ebd52b7694299b9566558b64d809c;m=16ffb7c;t=641e893289743;x=ca7606b463267f3b","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"24116092","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"24126155","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017403005","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b5;b=082ebd52b7694299b9566558b64d809c;m=17022cb;t=641e89328be7d;x=2cb5c1fa9579603d","_CAP_EFFECTIVE":"0","_UID":"10016","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.241224929Z\",\"ns\":\"Net.Handshake.Local.Receive.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@0\\\"}\",\"event\":\"Recv AnyMessage MsgProposeVersions (fromList [(NodeToClientV_16,TList [TInt 42,TBool False]),(NodeToClientV_17,TList [TInt 42,TBool False]),(NodeToClientV_18,TList [TInt 42,TBool False]),(NodeToClientV_19,TList [TInt 42,TBool False]),(NodeToClientV_20,TList [TInt 42,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"76\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1461","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017416321","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b6;b=082ebd52b7694299b9566558b64d809c;m=17056bc;t=641e89328f281;x=807e4d295dd7f0fe","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1462","SYSLOG_FACILITY":"3","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.256784728Z\",\"ns\":\"Net.Handshake.Local.Send.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@0\\\"}\",\"event\":\"Send AnyMessage MsgAcceptVersion NodeToClientV_20 (TList [TInt 42,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"76\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"24139452","_UID":"10016","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317017426556","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.25684563Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"networkMagic\":42,\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":20},\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"76\",\"host\":\"leios-node\"}","_GID":"10016","__MONOTONIC_TIMESTAMP":"24149684","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b7;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=b9a41c49c6b0fb3c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1463","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b8;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=31541c75cc8e88be","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017426556","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24149684","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_GID":"10016","_PID":"759","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.264469783Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1464","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_COMM":"cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5b9;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=6b3317a65a0ed7c","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.265219599Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":7,\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"24149684","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017426556","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__SEQNUM":"1465","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016"} +{"SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1466","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__MONOTONIC_TIMESTAMP":"24149684","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ba;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=5b46fe929b10cc50","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.265265415Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017426556","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317017426556","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.265303129Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"24149684","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1467","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5bb;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=19e92b7c3455d40f","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__SEQNUM":"1468","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5bc;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=207be40e14cbcd94","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.265361516Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"blockNo\":9,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":111},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24149684","_UID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317017426556","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016"} +{"__MONOTONIC_TIMESTAMP":"24149684","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1469","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.287239157Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317017426556","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5bd;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=c525d819538ce349","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service"} +{"_COMM":"cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.287657087Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"delay\":1364350.287458179,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017426556","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24149684","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5be;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=414e8173c0d82b66","__SEQNUM":"1470","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__SEQNUM":"1471","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5bf;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=ed6cdce64d6e4d45","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.288499373Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"75\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"24149684","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017426556","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3"} +{"__MONOTONIC_TIMESTAMP":"24149684","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017426556","_CAP_EFFECTIVE":"0","PRIORITY":"6","_COMM":"cardano-node","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.232653169Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM":"1472","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c0;b=082ebd52b7694299b9566558b64d809c;m=1707eb4;t=641e893291a7c;x=3c4c945583ae9b4e","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"24223338","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317017500210","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.290548516Z\",\"ns\":\"Net.InboundGovernor.Local.NewConnection\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"NewConnection\",\"provenance\":\"Inbound\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c1;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=8e9ef36422ebd3bd","PRIORITY":"6","__SEQNUM":"1473","SYSLOG_FACILITY":"3","_COMM":"cardano-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017500210","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c2;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=12c7985c808ca32f","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_GID":"10016","__MONOTONIC_TIMESTAMP":"24223338","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1474","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.293441901Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.293568174Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c3;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=67548fbbdabac19e","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24223338","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317017500210","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1475","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"24223338","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.297977114Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"delay\":1364344.287776656,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1476","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017500210","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c4;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=7dca514e11b46a24","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c5;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=45ace7b360974d68","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"24223338","_UID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.298091374Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM":"1477","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017500210","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_PID":"759","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__SEQNUM":"1478","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c6;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=15b77c3c984ac5e2","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.298172111Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"24223338","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317017500210","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c7;b=082ebd52b7694299b9566558b64d809c;m=1719e6a;t=641e8932a3a32;x=f7076e3405021473","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.298769952Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_GID":"10016","_UID":"10016","__SEQNUM":"1479","__REALTIME_TIMESTAMP":"1761317017500210","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"24223338","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c8;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=24f2703efc707b0f","_TRANSPORT":"stdout","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"24267858","SYSLOG_FACILITY":"3","_PID":"759","__SEQNUM":"1480","__REALTIME_TIMESTAMP":"1761317017544731","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.299182016Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016"} +{"__MONOTONIC_TIMESTAMP":"24267858","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1481","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5c9;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=73b8f52bfeba5cdb","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.303563858Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":8,\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317017544731","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_PID":"759","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ca;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=60d6a6575e15a77d","__SEQNUM":"1482","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.304695007Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"blockNo\":\"0\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017544731","_CAP_EFFECTIVE":"0","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"24267858","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.30479949Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__SEQNUM":"1483","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","__MONOTONIC_TIMESTAMP":"24267858","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5cb;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=a17da983731ffd88","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317017544731"} +{"_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.313533561Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"blockNo\":\"0\",\"kind\":\"AddedBlockToVolatileDB\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5cc;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=1ea6817e185ebccd","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_GID":"10016","_UID":"10016","__SEQNUM":"1484","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"24267858","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317017544731","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6"} +{"_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5cd;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=8ab52eaaa22f9df7","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_PID":"759","__REALTIME_TIMESTAMP":"1761317017544731","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1485","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.314028875Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"24267858","_COMM":"cardano-node"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"24267858","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.314169396Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017544731","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__SEQNUM":"1486","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ce;b=082ebd52b7694299b9566558b64d809c;m=1724c52;t=641e8932ae81b;x=f83d41ca63b1348b","_GID":"10016"} +{"_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24318205","__REALTIME_TIMESTAMP":"1761317017595078","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.316146462Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_PID":"759","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5cf;b=082ebd52b7694299b9566558b64d809c;m=17310fd;t=641e8932bacc6;x=c58712cffa2fed34","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__SEQNUM":"1487","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node"} +{"_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.316205688Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"blockNo\":10,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":148},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d0;b=082ebd52b7694299b9566558b64d809c;m=17310fd;t=641e8932bacc6;x=86ff4b9198a39c7e","_HOSTNAME":"leios-node","__SEQNUM":"1488","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24318205","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017595078"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.333117893Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"kind\":\"GenesisPoint\"},\"head\":{\"kind\":\"GenesisPoint\"}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017595078","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d1;b=082ebd52b7694299b9566558b64d809c;m=17310fd;t=641e8932bacc6;x=8e9954e4cc389fce","_PID":"759","__SEQNUM":"1489","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24318205","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d2;b=082ebd52b7694299b9566558b64d809c;m=17310fd;t=641e8932bacc6;x=b6ce7605b37bfbfb","__MONOTONIC_TIMESTAMP":"24318205","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM":"1490","__REALTIME_TIMESTAMP":"1761317017595078","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.333191925Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"Point\",\"slot\":2},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d3;b=082ebd52b7694299b9566558b64d809c;m=17310fd;t=641e8932bacc6;x=82b929916319771f","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1491","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.333469055Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_GID":"10016","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"24318205","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017595078","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759"} +{"_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017656090","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__MONOTONIC_TIMESTAMP":"24379236","__SEQNUM":"1492","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d4;b=082ebd52b7694299b9566558b64d809c;m=173ff64;t=641e8932c9b1a;x=2b679d34cacc3b3d","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.333496992Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1493","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__REALTIME_TIMESTAMP":"1761317017656090","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24379236","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d5;b=082ebd52b7694299b9566558b64d809c;m=173ff64;t=641e8932c9b1a;x=976a1468c7bc744b","_GID":"10016","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.334978465Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__SEQNUM":"1494","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017673308","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_UID":"10016","__MONOTONIC_TIMESTAMP":"24396436","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d6;b=082ebd52b7694299b9566558b64d809c;m=1744294;t=641e8932cde5c;x=307cf85e9c34bc00","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.33500277Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToWarmRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"PromotedToWarmRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundIdleSt\"}}},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335026236Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":1},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1496","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24413623","__REALTIME_TIMESTAMP":"1761317017690495","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d8;b=082ebd52b7694299b9566558b64d809c;m=17485b7;t=641e8932d217f;x=a973cafa539beaf","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","PRIORITY":"6"} +{"_UID":"10016","_PID":"759","__REALTIME_TIMESTAMP":"1761317017697761","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__SEQNUM":"1497","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5d9;b=082ebd52b7694299b9566558b64d809c;m=174a22e;t=641e8932d3de1;x=85ac79e51f4e2ed3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335049424Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"RemoteWarmSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"24420910","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335412598Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017705838","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"24428966","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_UID":"10016","__SEQNUM":"1498","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5da;b=082ebd52b7694299b9566558b64d809c;m=174c1a6;t=641e8932d5d6e;x=827701273dff3e4b","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"24435286","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM":"1499","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335694757Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":9,\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5db;b=082ebd52b7694299b9566558b64d809c;m=174da56;t=641e8932d761e;x=633da3e659d6e08c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_PID":"759","_GID":"10016","__REALTIME_TIMESTAMP":"1761317017712158","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system"} +{"__REALTIME_TIMESTAMP":"1761317017722766","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1500","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.33574616Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5dc;b=082ebd52b7694299b9566558b64d809c;m=17503d7;t=641e8932d9f8e;x=d3b61443a48d5b69","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24445911","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__SEQNUM":"1501","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335786109Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24452663","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5dd;b=082ebd52b7694299b9566558b64d809c;m=1751e37;t=641e8932db9ff;x=e830b9711e92292f","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317017729535"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.335845894Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"blockNo\":11,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":162},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1502","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"24452663","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5de;b=082ebd52b7694299b9566558b64d809c;m=1751e37;t=641e8932db9ff;x=f9be1e125634a88a","__REALTIME_TIMESTAMP":"1761317017729535","_CAP_EFFECTIVE":"0","_UID":"10016","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"24452663","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017729535","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5df;b=082ebd52b7694299b9566558b64d809c;m=1751e37;t=641e8932db9ff;x=7215d7b8b6c82d4c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_GID":"10016","__SEQNUM":"1503","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.336014071Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.344434136Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToHotRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"PromotedToHotRemote\"},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317017762178","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e1;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=bba10235652923fe","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"24485310","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1505"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.34446738Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":1,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"24485310","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017762178","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e2;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=ead166507e6a4361","__SEQNUM":"1506","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e3;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=83d44f37714ff33e","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317017762178","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"24485310","_CAP_EFFECTIVE":"0","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.344490568Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"RemoteHotSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__SEQNUM":"1507","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.344638072Z\",\"ns\":\"StateQueryServer.Receive.Acquire\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgAcquire\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"24485310","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317017762178","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e4;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=c54260cde32bc1a8","__SEQNUM":"1508","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_PID":"759","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317017762178","_UID":"10016","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e5;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=71b9020a2079a309","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1509","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.344760993Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"24485310"} +{"_GID":"10016","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24485310","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1510","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.344823291Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017762178","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e6;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=c8b14e879b63b7fe"} +{"_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1511","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317017762178","__MONOTONIC_TIMESTAMP":"24485310","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e7;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=4459fe502de60110","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.382552668Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_PID":"759"} +{"__REALTIME_TIMESTAMP":"1761317017762178","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.391643488Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM":"1512","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__MONOTONIC_TIMESTAMP":"24485310","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e8;b=082ebd52b7694299b9566558b64d809c;m=1759dbe;t=641e8932e3982;x=4224994d54f76c12","PRIORITY":"6"} +{"_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_UID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317017820772","__SEQNUM":"1513","_PID":"759","__MONOTONIC_TIMESTAMP":"24543900","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5e9;b=082ebd52b7694299b9566558b64d809c;m=176829c;t=641e8932f1e64;x=3483d07c3a07572e","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.443121259Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ea;b=082ebd52b7694299b9566558b64d809c;m=176829c;t=641e8932f1e64;x=d3bebf2084599cea","__SEQNUM":"1514","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317017820772","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.443383025Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":10,\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"24543900","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM":"1515","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317017820772","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.443457336Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24543900","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5eb;b=082ebd52b7694299b9566558b64d809c;m=176829c;t=641e8932f1e64;x=2a4886ac96e8e4ec"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"24543900","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.443512091Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM":"1516","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ec;b=082ebd52b7694299b9566558b64d809c;m=176829c;t=641e8932f1e64;x=104ca9babdf6d3d9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","PRIORITY":"6","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017820772","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_UID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1517","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ed;b=082ebd52b7694299b9566558b64d809c;m=176829c;t=641e8932f1e64;x=7faf9b878e017db5","_CAP_EFFECTIVE":"0","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017820772","__MONOTONIC_TIMESTAMP":"24543900","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.443589755Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"blockNo\":12,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":179},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__MONOTONIC_TIMESTAMP":"24583443","_CAP_EFFECTIVE":"0","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317017860315","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.46823311Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"BlockPoint\",\"slot\":2},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1519","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ef;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=8fc76c64b1e0dc45","_TRANSPORT":"stdout"} +{"_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317017860315","_UID":"10016","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f0;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=ffbb60b9ef5ef4d2","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__MONOTONIC_TIMESTAMP":"24583443","__SEQNUM":"1520","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.479681772Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__SEQNUM":"1521","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.512248202Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"24583443","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317017860315","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f1;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=2b9a089446b134c5","PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__REALTIME_TIMESTAMP":"1761317017860315","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f2;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=f838d7d99418532e","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519040685Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":11,\"headerHash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__SEQNUM":"1522","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24583443","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_PID":"759","_HOSTNAME":"leios-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317017860315","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f3;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=6353bee6053fe47d","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"24583443","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519085104Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1523"} +{"__MONOTONIC_TIMESTAMP":"24583443","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519112761Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317017860315","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f4;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=473942fd8463232a","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1524","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1525","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","PRIORITY":"6","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"24583443","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f5;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=a777821fb98250bf","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519156622Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"blockNo\":13,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":183},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317017860315","_UID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317017860315","_GID":"10016","__SEQNUM":"1526","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f6;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=48b0c1935ca4ace1","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"24583443","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519285409Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":183},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519644114Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317017860315","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f7;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=a315788a806196d2","__SEQNUM":"1527","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"24583443","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_UID":"10016","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__SEQNUM":"1528","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.519681549Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_PID":"759","__REALTIME_TIMESTAMP":"1761317017860315","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f8;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=9ec57aa3f89e7656","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"24583443","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1529","__REALTIME_TIMESTAMP":"1761317017860315","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5f9;b=082ebd52b7694299b9566558b64d809c;m=1771d13;t=641e8932fb8db;x=ac5035171e6b2c87","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"24583443","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.533307861Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}"} +{"SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"24664279","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_GID":"10016","_RUNTIME_SCOPE":"system","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:37.19840133 UTC to 2025-10-24 14:43:37.873102724 UTC","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1531","__REALTIME_TIMESTAMP":"1761317017941152","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5fb;b=082ebd52b7694299b9566558b64d809c;m=17858d7;t=641e89330f4a0;x=503984f79683bf8a","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.551056765Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":0,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":2,\"tieBreakVRF\":\"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf\"},\"newtip\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2\"},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317017941152","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1532","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5fc;b=082ebd52b7694299b9566558b64d809c;m=17858d7;t=641e89330f4a0;x=d8c5135a62364343","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"24664279"} +{"_PID":"759","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM":"1533","_RUNTIME_SCOPE":"system","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.579398077Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5fd;b=082ebd52b7694299b9566558b64d809c;m=17858d7;t=641e89330f4a0;x=21f639688a2a7bb8","__REALTIME_TIMESTAMP":"1761317017941152","__MONOTONIC_TIMESTAMP":"24664279","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3"} +{"_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.579551448Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317017964741","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5fe;b=082ebd52b7694299b9566558b64d809c;m=178b4ff;t=641e8933150c5;x=a20fefa5d48b380d","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"24687871","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1534","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6"} +{"_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=5ff;b=082ebd52b7694299b9566558b64d809c;m=178b4ff;t=641e8933150c5;x=50c697aa967f9d2b","SYSLOG_FACILITY":"3","_PID":"759","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317017964741","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.646418047Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__SEQNUM":"1535","__MONOTONIC_TIMESTAMP":"24687871","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24687871","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__SEQNUM":"1536","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317017964741","PRIORITY":"6","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.646507723Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=600;b=082ebd52b7694299b9566558b64d809c;m=178b4ff;t=641e8933150c5;x=a4cb88ce7430c6f","_UID":"10016","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=601;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=b82e3544f6825d33","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"24725372","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.646564435Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1537","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","_GID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317018002241","_RUNTIME_SCOPE":"system"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.649099394Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016","__MONOTONIC_TIMESTAMP":"24725372","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018002241","__SEQNUM":"1538","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=602;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=3407d5a5c79b7cd0","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system"} +{"__SEQNUM":"1539","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=603;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=683f49206afb235d","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317018002241","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24725372","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.650307089Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.652092791Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8@2\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__SEQNUM":"1540","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=604;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=bac8c23058bff604","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"24725372","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317018002241","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018002241","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__SEQNUM":"1541","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.652232194Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=605;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=c35fece863b30f9a","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24725372"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018002241","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"24725372","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=606;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=dfddf2c879ebe133","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.652264042Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_GID":"10016","__SEQNUM":"1542"} +{"_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.652342264Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"blockNo\":\"1\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317018002241","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1543","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24725372","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=607;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=1653610b70c75789"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.663412106Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"24725372","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018002241","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__SEQNUM":"1544","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","PRIORITY":"6","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=608;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=703736cd224d01a1","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1545","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317018002241","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"24725372","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.672002863Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"blockNo\":\"1\",\"kind\":\"AddedBlockToVolatileDB\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=609;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=9a36fb705b55912c","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317018002241","__SEQNUM":"1546","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.672211549Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"kind\":\"GenesisPoint\"},\"head\":{\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"BlockPoint\",\"slot\":2}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"24725372","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60a;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=7d65bd7c7ba1bd81","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_UID":"10016"} +{"_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"24725372","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.672282508Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"Point\",\"slot\":44},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_GID":"10016","__SEQNUM":"1547","_PID":"759","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018002241","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60b;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=bfc5450bbefa9525"} +{"_UID":"10016","__REALTIME_TIMESTAMP":"1761317018002241","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60c;b=082ebd52b7694299b9566558b64d809c;m=179477c;t=641e89331e341;x=837a0e2a4771bdcd","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24725372","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1548","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.672369111Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service"} +{"_UID":"10016","__MONOTONIC_TIMESTAMP":"24816418","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60d;b=082ebd52b7694299b9566558b64d809c;m=17aab22;t=641e8933346e8;x=d2005c0fad326da7","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM":"1549","_GID":"10016","__REALTIME_TIMESTAMP":"1761317018093288","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.672404031Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759"} +{"_PID":"759","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018093288","__SEQNUM":"1550","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.682711207Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60e;b=082ebd52b7694299b9566558b64d809c;m=17aab22;t=641e8933346e8;x=e2a3a52d58289c7","__MONOTONIC_TIMESTAMP":"24816418","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=60f;b=082ebd52b7694299b9566558b64d809c;m=17aab22;t=641e8933346e8;x=db0c684405065cb9","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"24816418","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317018093288","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1551","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.682751995Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016"} +{"__REALTIME_TIMESTAMP":"1761317018093288","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.705601267Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","PRIORITY":"6","_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1552","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=610;b=082ebd52b7694299b9566558b64d809c;m=17aab22;t=641e8933346e8;x=593a34bcef384c45","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24816418","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__SEQNUM":"1553","__MONOTONIC_TIMESTAMP":"24816418","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.718601802Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"BlockPoint\",\"slot\":44},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=611;b=082ebd52b7694299b9566558b64d809c;m=17aab22;t=641e8933346e8;x=a39c3a67fbaaa56b","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317018093288","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"24848584","__SEQNUM":"1554","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__REALTIME_TIMESTAMP":"1761317018125457","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=612;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=44120b83fdb59f44","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.721986869Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":1,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":44,\"tieBreakVRF\":\"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951\"},\"newtip\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44\",\"oldTipSelectView\":{\"chainLength\":0,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":2,\"tieBreakVRF\":\"9a6d991507a21ed626ddc979ba5c0a2b727efea1c14a8c8edd9885ac40f1ac263d2e42985645f5b8c53eb56c7c9bc8c48267ff59c43a7759a952dbde67aaa0cf\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_PID":"759","__REALTIME_TIMESTAMP":"1761317018125457","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=613;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=a1b49e9960b6d426","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM":"1555","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.722160076Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4@44\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24848584","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"24848584","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1556","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.722245841Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317018125457","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=614;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=43bc4a9c2201eed8","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=615;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=385a6fd9d9b80054","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.722270984Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"Point\",\"slot\":52},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__MONOTONIC_TIMESTAMP":"24848584","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018125457","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1557"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=616;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=7ae5150593f71eb4","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.72232127Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"Point\",\"slot\":52},\"blockNo\":\"2\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_PID":"759","__MONOTONIC_TIMESTAMP":"24848584","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317018125457","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1558"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1559","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018125457","_PID":"759","__MONOTONIC_TIMESTAMP":"24848584","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.744770771Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":183},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=617;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=5e310401f203d139","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_GID":"10016","_RUNTIME_SCOPE":"system","_UID":"10016","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.750197718Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"Point\",\"slot\":52},\"blockNo\":\"2\",\"kind\":\"AddedBlockToVolatileDB\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=618;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=ea372d0e5925cf1e","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1560","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"24848584","__REALTIME_TIMESTAMP":"1761317018125457","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"SYSLOG_FACILITY":"3","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.756568639Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"kind\":\"GenesisPoint\"},\"head\":{\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"BlockPoint\",\"slot\":44}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM":"1561","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24848584","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=619;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=99e11e1ee3453704","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018125457","_HOSTNAME":"leios-node","_TRANSPORT":"stdout"} +{"__REALTIME_TIMESTAMP":"1761317018125457","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61a;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=c7af69a123ec37dd","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.756661947Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"Point\",\"slot\":52},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1562","_PID":"759","_GID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"24848584","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout"} +{"_GID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_PID":"759","_COMM":"cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61b;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=69c59d1f1ffc1cbd","__REALTIME_TIMESTAMP":"1761317018125457","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1563","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"24848584","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.756735979Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"24848584","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317018125457","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1564","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61c;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=7d6af7c81eb7d816","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.756762518Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61d;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=780c68ebc13235a2","__REALTIME_TIMESTAMP":"1761317018125457","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.757343039Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"Point\",\"slot\":179},\"kind\":\"AddedBlockToQueue\",\"queueSize\":10},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1565","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"24848584","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node"} +{"__MONOTONIC_TIMESTAMP":"24848584","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018125457","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.75753161Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61e;b=082ebd52b7694299b9566558b64d809c;m=17b28c8;t=641e89333c491;x=db658f1674f17a37","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__SEQNUM":"1566","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"24934821","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1567","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.781651436Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018211694","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=61f;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=bd4254ecdebe9f2c","_UID":"10016","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__MONOTONIC_TIMESTAMP":"24934821","_GID":"10016","__SEQNUM":"1568","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=620;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=89753d445a1beba5","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.794783552Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"BlockPoint\",\"slot\":52},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018211694","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=621;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=c608d60f12718c6a","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.808550665Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":2,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":52,\"tieBreakVRF\":\"a7ebd222c942746c013165f0adc2abfec5f1d25f7b41b2aef928ab4c865f1b48775a18e1699e447b118e89591d663968990ef90f7807b5b2a4295561b0264d69\"},\"newtip\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52\",\"oldTipSelectView\":{\"chainLength\":1,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":44,\"tieBreakVRF\":\"a5891dd8a1fd532d673f2ad6f619abc677fd98221e160a461bdf681f371d443ffee28f1d4f5cebfaaae3b7694b63547250cb6a9ab2c7826079574afb13085951\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018211694","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24934821","_GID":"10016","__SEQNUM":"1569","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node"} +{"_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018211694","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"24934821","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM":"1570","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=622;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=a686ff9bbc6e0275","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.818363644Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018211694","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__SEQNUM":"1571","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=623;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=dbd6802589a1ca70","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"24934821","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.782264922Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":12,\"headerHash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","PRIORITY":"6"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=624;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=52c13f077f32914d","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018211694","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"24934821","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__SEQNUM":"1572","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.819991225Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_COMM":"cardano-node"} +{"__REALTIME_TIMESTAMP":"1761317018211694","__MONOTONIC_TIMESTAMP":"24934821","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=625;b=082ebd52b7694299b9566558b64d809c;m=17c79a5;t=641e89335156e;x=56df054d3d1731a3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.820027822Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1573","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.820077269Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"blockNo\":14,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":187},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018269283","_UID":"10016","__SEQNUM":"1574","_TRANSPORT":"stdout","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"24992411","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=626;b=082ebd52b7694299b9566558b64d809c;m=17d5a9b;t=641e89335f663;x=47564e9167742495","PRIORITY":"6"} +{"_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.872110139Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8@52\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25000071","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=627;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=ff1c4fdd34fa230a","__SEQNUM":"1575","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018276942","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_UID":"10016","_HOSTNAME":"leios-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018276942","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=628;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=ec765cfe8db5b9b9","_UID":"10016","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.873070038Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"25000071","__SEQNUM":"1576","_HOSTNAME":"leios-node","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=629;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=59eba0d416e7f5a8","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.873102724Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"Point\",\"slot\":53},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018276942","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25000071","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM":"1577","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018276942","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25000071","__SEQNUM":"1578","_UID":"10016","_CAP_EFFECTIVE":"0","_PID":"759","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.873347168Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"kind\":\"GenesisPoint\"},\"head\":{\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"BlockPoint\",\"slot\":52}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62a;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=2a4cf2d50f297d9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system"} +{"SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1579","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62b;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=5c78f9cbe0822f6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018276942","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.873571778Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"Point\",\"slot\":53},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"25000071","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1580","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25000071","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.873634914Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018276942","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62c;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=690027d545b9ff3b","_SYSTEMD_SLICE":"system.slice","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__MONOTONIC_TIMESTAMP":"25000071","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.900252822Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317018276942","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62d;b=082ebd52b7694299b9566558b64d809c;m=17d7887;t=641e89336144e;x=9d1b182de502e451","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__SEQNUM":"1581","_PID":"759","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62e;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=7eee6c915ce38357","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"25041583","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__SEQNUM":"1582","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_TRANSPORT":"stdout","PRIORITY":"6","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018318456","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.909281065Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=62f;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=31f542defb68927f","_GID":"10016","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018318456","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1583","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.938374986Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"25041583","_COMM":"cardano-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.938989589Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=630;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=57e7144b43520c0c","PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1584","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25041583","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317018318456","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_UID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.939151062Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":13,\"headerHash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1585","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=631;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=f860ef38229b20b4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018318456","_HOSTNAME":"leios-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"25041583","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25041583","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=632;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=16bdd37e14041f07","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018318456","_GID":"10016","__SEQNUM":"1586","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.958261871Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759"} +{"_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_PID":"759","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.95833283Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=633;b=082ebd52b7694299b9566558b64d809c;m=17e1aaf;t=641e89336b678;x=1dde1cfc97797aa6","__REALTIME_TIMESTAMP":"1761317018318456","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25041583","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM":"1587","_RUNTIME_SCOPE":"system"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317018352885","__MONOTONIC_TIMESTAMP":"25076059","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_GID":"10016","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=634;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=71784c239840a944","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1588","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.974328997Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node"} +{"PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=635;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=7bf263481c59f6f4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.974796654Z\",\"ns\":\"StateQueryServer.Receive.Release\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgRelease\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1589","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"25076059","__REALTIME_TIMESTAMP":"1761317018352885","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_SLICE":"system.slice","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=636;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=611ee36cb6f57f81","__REALTIME_TIMESTAMP":"1761317018352885","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","SYSLOG_FACILITY":"3","__SEQNUM":"1590","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.974856159Z\",\"ns\":\"StateQueryServer.Receive.Done\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgDone\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"}},\"sev\":\"Info\",\"thread\":\"79\",\"host\":\"leios-node\"}","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"25076059","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1591","_HOSTNAME":"leios-node","_UID":"10016","_PID":"759","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25076059","__REALTIME_TIMESTAMP":"1761317018352885","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=637;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=425a0889af76847","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.990545024Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}"} +{"_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=638;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=960ba47c6965f693","__SEQNUM":"1592","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_PID":"759","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25076059","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317018352885","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.990706777Z\",\"ns\":\"Net.InboundGovernor.Local.WaitIdleRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"WaitIdleRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundSt\"}}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.991244554Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"BlockPoint\",\"slot\":53},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018352885","__MONOTONIC_TIMESTAMP":"25076059","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1593","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=639;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=ae41d5eeb02c5503","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1594","__MONOTONIC_TIMESTAMP":"25076059","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.991485088Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":3,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":53,\"tieBreakVRF\":\"4c0c5eb5ba7015fe3da918899131fbe585560db7ba3df5f6e3fef69c9b8e545b86914011d4d69c2d143b66a9f87def6276d775988281818c071068320a0b045a\"},\"newtip\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53\",\"oldTipSelectView\":{\"chainLength\":2,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":52,\"tieBreakVRF\":\"a7ebd222c942746c013165f0adc2abfec5f1d25f7b41b2aef928ab4c865f1b48775a18e1699e447b118e89591d663968990ef90f7807b5b2a4295561b0264d69\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63a;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=df66f9a4d6541c01","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018352885","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"25076059","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.99166025Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59@53\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63b;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=65f074e9fa433692","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018352885","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node","__SEQNUM":"1595","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25076059","_UID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63c;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=3c4855be94c38700","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1596","__REALTIME_TIMESTAMP":"1761317018352885","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.991774789Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317018352885","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63d;b=082ebd52b7694299b9566558b64d809c;m=17ea15b;t=641e893373cf5;x=f9d96bf9290275c0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25076059","_UID":"10016","_COMM":"cardano-node","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__SEQNUM":"1597","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_GID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.991814739Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"Point\",\"slot\":59},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1598","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63e;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=703d129e82277137","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25149688","__REALTIME_TIMESTAMP":"1761317018426561","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.99204717Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}"} +{"_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018426561","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_COMM":"cardano-node","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=63f;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=e9a06dc7f3f2dd55","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1599","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25149688","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.992114497Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_GID":"10016","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25149688","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=640;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=1612ec436d2ea666","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1600","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.992563437Z\",\"ns\":\"Net.InboundGovernor.Local.ResponderRestarted\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"ResponderStarted\",\"miniProtocolNum\":{\"kind\":\"MiniProtocolNum\",\"num\":7}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018426561","_UID":"10016","_PID":"759","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"SYSLOG_FACILITY":"3","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.992770167Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"25149688","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018426561","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=641;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=7f23b7a0039f2268","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1601","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_CAP_EFFECTIVE":"0","_GID":"10016","_UID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:37.994543577Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=642;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=b2f65fe83b3b8e41","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1602","__REALTIME_TIMESTAMP":"1761317018426561","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","_PID":"759","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25149688","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=643;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=1ace330ddfbd1adf","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25149688","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018426561","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1603","_CAP_EFFECTIVE":"0","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.994858142Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018426561","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.995428885Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"blockNo\":15,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":188},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_PID":"759","__SEQNUM":"1604","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=644;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=2657bf610ee40e32","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"25149688","PRIORITY":"6","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016"} +{"_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25149688","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=645;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=9f0c5048161d98e8","PRIORITY":"6","_COMM":"cardano-node","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:37.99359625Z\",\"ns\":\"Net.Mux.Local.CleanExit\",\"data\":{\"bearer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@0\\\"\"},\"event\":{\"kind\":\"Mux.TraceCleanExit\",\"miniProtocolDir\":\"ResponderDir\",\"miniProtocolNum\":\"MiniProtocolNum 7\",\"msg\":\"Miniprotocol terminated cleanly\"},\"kind\":\"Mux.Trace\"},\"sev\":\"Notice\",\"thread\":\"76\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__SEQNUM":"1605","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018426561","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=646;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=843aabf06ac53ecf","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018426561","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_GID":"10016","__SEQNUM":"1606","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25149688","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.02041586Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"BlockPoint\",\"slot\":2}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","PRIORITY":"6","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1607","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=647;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=ba1535be7f3c3996","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317018426561","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.020486539Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":2}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"25149688"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.091968529Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317018426561","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25149688","_PID":"759","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=648;b=082ebd52b7694299b9566558b64d809c;m=17fc0f8;t=641e893385cc1;x=286f79f2cd90bfc6","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1608","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice"} +{"__REALTIME_TIMESTAMP":"1761317018503843","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=649;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=bfee2f286c01bbbd","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__SEQNUM":"1609","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092033901Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25226971","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__SEQNUM":"1610","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64a;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=13455937116a4f0f","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018503843","_PID":"759","__MONOTONIC_TIMESTAMP":"25226971","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092335056Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"4e93dab121aaeabf20a6b6112048260fb1b72ed94f10eb2f331d79015bb447e8\",\"kind\":\"BlockPoint\",\"slot\":2},\"head\":{\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"BlockPoint\",\"slot\":53}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25226971","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64b;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=34818d2c25415bb2","SYSLOG_FACILITY":"3","__SEQNUM":"1611","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092374447Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"Point\",\"slot\":59},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018503843"} +{"_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64c;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=36f422f3119a3ce4","__SEQNUM":"1612","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092430599Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25226971","__REALTIME_TIMESTAMP":"1761317018503843","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0"} +{"_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317018503843","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092451272Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__SEQNUM":"1613","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64d;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=65aff2f6fc2885e8","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25226971","_PID":"759"} +{"__SEQNUM":"1614","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64e;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=e1e6418dc9a98830","_PID":"759","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25226971","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.09249625Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018503843","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_TRANSPORT":"stdout","_GID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1615","__REALTIME_TIMESTAMP":"1761317018503843","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=64f;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=831d702b3808d02f","SYSLOG_FACILITY":"3","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25226971","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_UID":"10016","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092766117Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"delay\":1364221.092597101,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1616","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018503843","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25226971","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=650;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=fe3aae0e2929f133","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.092829532Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"PRIORITY":"6","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=651;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=5b7bf53f85462516","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.106455845Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1617","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25226971","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018503843","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_UID":"10016","__REALTIME_TIMESTAMP":"1761317018503843","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=652;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=cd5fc878ff5633cb","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.106662296Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":14,\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1618","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25226971","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node"} +{"_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.106711744Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1619","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"25226971","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=653;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=a5037f95ebd1595d","_PID":"759","__REALTIME_TIMESTAMP":"1761317018503843","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25226971","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__REALTIME_TIMESTAMP":"1761317018503843","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=654;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=bdccec101ae44fd1","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.106749737Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1620","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__MONOTONIC_TIMESTAMP":"25226971","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.106808683Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"blockNo\":16,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":222},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_COMM":"cardano-node","__SEQNUM":"1621","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=655;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=1d6321ec9a13dcef","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317018503843"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=656;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=598e23f1955fcbd","_UID":"10016","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.169754114Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018503843","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__SEQNUM":"1622","__MONOTONIC_TIMESTAMP":"25226971","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=657;b=082ebd52b7694299b9566558b64d809c;m=180eedb;t=641e893398aa3;x=78684507af46887b","__MONOTONIC_TIMESTAMP":"25226971","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.169838482Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__SEQNUM":"1623","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_PID":"759","__REALTIME_TIMESTAMP":"1761317018503843"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.206762169Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1624","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"25325198","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317018602068","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=658;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=5704ecbb221f3d3f","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_PID":"759","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.169877314Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_PID":"759","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"25325198","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018602068","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1625","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=659;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=4ceff8a99b19bc33","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"1626","_GID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.224434527Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"BlockPoint\",\"slot\":59},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018602068","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25325198","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65a;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=48ca940ea1d76049","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.224579238Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":4,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":59,\"tieBreakVRF\":\"263b9f9d16d7bf1a7f540d257bf74e4f86c172719b84db889be808775165cab9872c9e985c644f01a2a987be20e9e730e3033ca4adb3bf55122941675ea8a8a4\"},\"newtip\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59\",\"oldTipSelectView\":{\"chainLength\":3,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":53,\"tieBreakVRF\":\"4c0c5eb5ba7015fe3da918899131fbe585560db7ba3df5f6e3fef69c9b8e545b86914011d4d69c2d143b66a9f87def6276d775988281818c071068320a0b045a\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"25325198","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65b;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=35fbf6a8cf54f7ee","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018602068","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1627","_TRANSPORT":"stdout","_COMM":"cardano-node"} +{"__REALTIME_TIMESTAMP":"1761317018602068","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25325198","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1628","_GID":"10016","_HOSTNAME":"leios-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65c;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=b40fb3b4eeeddc70","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.257298201Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":15,\"headerHash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","PRIORITY":"6"} +{"_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65d;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=2a78a699b469cb9b","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.257342899Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","__SEQNUM":"1629","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25325198","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018602068"} +{"_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25325198","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018602068","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.257371953Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1630","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65e;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=5f68c54fd140cf4","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018602068","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_GID":"10016","__SEQNUM":"1631","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=65f;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=ba30d9bc71d2502e","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.25741721Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"blockNo\":17,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":247},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25325198","_CAP_EFFECTIVE":"0"} +{"_UID":"10016","__REALTIME_TIMESTAMP":"1761317018602068","_PID":"759","__MONOTONIC_TIMESTAMP":"25325198","PRIORITY":"6","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=660;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=f58ac49def3d7e35","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.257770607Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":247},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1632"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1633","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.341294072Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e@59\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=661;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=62de5316d25df5dc","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","__MONOTONIC_TIMESTAMP":"25325198","__REALTIME_TIMESTAMP":"1761317018602068","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_COMM":"cardano-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25325198","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_RUNTIME_SCOPE":"system","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018602068","_COMM":"cardano-node","__SEQNUM":"1634","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.341389894Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=662;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=20c198f347ef99ce","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM":"1635","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25325198","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=663;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=77d08a8792822971","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018602068","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.341417551Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"Point\",\"slot\":77},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018602068","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=664;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=ab26ff543fb18f14","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25325198","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM":"1636","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.341487672Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"Point\",\"slot\":77},\"blockNo\":\"5\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317018602068","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"25325198","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.357847293Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":152541760,\"CentiBlkIO\":0,\"CentiCpu\":75,\"CentiGC\":0,\"CentiMut\":68,\"FsRd\":50733056,\"FsWr\":24576,\"GcsMajor\":1,\"GcsMinor\":4,\"Heap\":45088768,\"Live\":4097320,\"NetRd\":0,\"NetWr\":0,\"RSS\":94371840,\"Threads\":10,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=665;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=a366f09863700995","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__SEQNUM":"1637","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","PRIORITY":"6"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_COMM":"cardano-node","PRIORITY":"6","_GID":"10016","__REALTIME_TIMESTAMP":"1761317018602068","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25325198","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=666;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=70dad7f7dc7b787e","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.372266444Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__SEQNUM":"1638","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1639","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25325198","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=667;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=2ba1a0e569918a6c","__REALTIME_TIMESTAMP":"1761317018602068","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.39283051Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"BlockPoint\",\"slot\":44},\"head\":{\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"BlockPoint\",\"slot\":59}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system"} +{"_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018602068","__MONOTONIC_TIMESTAMP":"25325198","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.409381496Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=668;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=e93877a4be921f9d","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1640","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1641","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25325198","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317018602068","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=669;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=5d902401e355b8b2","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.409457484Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_PID":"759","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66a;b=082ebd52b7694299b9566558b64d809c;m=1826e8e;t=641e8933b0a54;x=cb0f96f86220ee29","__REALTIME_TIMESTAMP":"1761317018602068","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__SEQNUM":"1642","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.409553585Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25325198"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66b;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=f9f7821a745782b0","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1643","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25455448","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.409808087Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"Point\",\"slot\":187},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018732320","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66c;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=55f9015df2be3e68","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.460595547Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"bd384ce8792d89da9ab6d11d10fc70a36a2899e6c3b10d936376922a4dbfd4d4\",\"kind\":\"BlockPoint\",\"slot\":44}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM":"1644","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317018732320","__MONOTONIC_TIMESTAMP":"25455448","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.460649465Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":44}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66d;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=a50f14816055ac7c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"25455448","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__SEQNUM":"1645","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018732320","_UID":"10016","PRIORITY":"6"} +{"_COMM":"cardano-node","PRIORITY":"6","_PID":"759","__SEQNUM":"1646","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66e;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=21c59baf3f3afb5a","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.46070422Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"Point\",\"slot\":77},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25455448","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018732320","_RUNTIME_SCOPE":"system","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_GID":"10016","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317018732320","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=66f;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=fbb4e2be2639de2","__MONOTONIC_TIMESTAMP":"25455448","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1647","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.460769871Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM":"1648","__REALTIME_TIMESTAMP":"1761317018732320","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25455448","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.460791662Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=670;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=2b6650ac3c64c0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25455448","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=671;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=b939b20e0e7333a2","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317018732320","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.468311891Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM":"1649","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317018732320","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"25455448","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=672;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=1576e0262b321e99","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1650","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.468376704Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_CAP_EFFECTIVE":"0"} +{"_HOSTNAME":"leios-node","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.468757479Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=673;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=1f02b7a148bacbfa","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"25455448","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018732320","__SEQNUM":"1651","_COMM":"cardano-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM":"1652","__REALTIME_TIMESTAMP":"1761317018732320","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.600454663Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=674;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=a7978778968fd04a","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"25455448","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25455448","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=675;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=323a81090f23367f","_TRANSPORT":"stdout","_PID":"759","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.560938189Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"BlockPoint\",\"slot\":77},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018732320","_COMM":"cardano-node","__SEQNUM":"1653"} +{"_PID":"759","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25455448","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__SEQNUM":"1654","_RUNTIME_SCOPE":"system","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018732320","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.601146371Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":5,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":77,\"tieBreakVRF\":\"eb8dc698abfd6a3394a29bb45182af6b8136999142a0b290e83cb92575a4f27f8aa8b27e08b0b32cad70ad57666b34a6e18e24408b20004fe8c7125889059d4e\"},\"newtip\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77\",\"oldTipSelectView\":{\"chainLength\":4,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":59,\"tieBreakVRF\":\"263b9f9d16d7bf1a7f540d257bf74e4f86c172719b84db889be808775165cab9872c9e985c644f01a2a987be20e9e730e3033ca4adb3bf55122941675ea8a8a4\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=676;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=643d90e519c383c4","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"25455448","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.601311476Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37@77\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317018732320","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=677;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=8d269f87a6ad61fa","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__SEQNUM":"1655","_RUNTIME_SCOPE":"system","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.601417076Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM":"1656","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"25455448","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=678;b=082ebd52b7694299b9566558b64d809c;m=1846b58;t=641e8933d0720;x=ed6e70566c41681f","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317018732320","PRIORITY":"6","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25539768","_HOSTNAME":"leios-node","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM":"1657","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=679;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=e1c3500ff8afa663","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.6014506Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"Point\",\"slot\":80},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018816640","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system"} +{"__SEQNUM":"1658","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67a;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=384b824561c1a361","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__MONOTONIC_TIMESTAMP":"25539768","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317018816640","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.658525172Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":247},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_GID":"10016","_TRANSPORT":"stdout","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.688711411Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317018816640","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__MONOTONIC_TIMESTAMP":"25539768","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67b;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=fb318360a8086323","_COMM":"cardano-node","_UID":"10016","PRIORITY":"6","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1659","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1660","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317018816640","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25539768","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.694724466Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":16,\"headerHash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67c;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=3598ec54c82e4c73","_UID":"10016","_PID":"759","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__SEQNUM":"1661","__REALTIME_TIMESTAMP":"1761317018816640","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67d;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=72448aeca1170c8d","__MONOTONIC_TIMESTAMP":"25539768","_TRANSPORT":"stdout","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.701611095Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"delay\":1364182.600608873,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":862},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_HOSTNAME":"leios-node"} +{"_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317018816640","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1662","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_GID":"10016","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.701698537Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25539768","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67e;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=a43c64a1120fb7dc","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.715710653Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"BlockPoint\",\"slot\":52},\"head\":{\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"BlockPoint\",\"slot\":77}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=67f;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=ece4469831c1f6f1","PRIORITY":"6","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317018816640","__SEQNUM":"1663","_PID":"759","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"25539768","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018816640","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_HOSTNAME":"leios-node","PRIORITY":"6","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.715774348Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"Point\",\"slot\":80},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"1664","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"25539768","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=680;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=2d1cef298e08d9f1","_PID":"759"} +{"_RUNTIME_SCOPE":"system","__SEQNUM":"1665","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_GID":"10016","__MONOTONIC_TIMESTAMP":"25539768","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.715839719Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=681;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=df3eba25f9932abf","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317018816640","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_UID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM":"1666","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=682;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=35f091a62013deaf","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317018816640","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.71586151Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_PID":"759","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"25539768","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.744292777Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=683;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=4287f7d20783f3dd","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1667","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317018816640","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25539768"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1668","__REALTIME_TIMESTAMP":"1761317018816640","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=684;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=265302939c0c5268","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"25539768","_GID":"10016","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.744462631Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\",\"kind\":\"BlockPoint\",\"slot\":52}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018816640","__MONOTONIC_TIMESTAMP":"25539768","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.744504256Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":52}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_FACILITY":"3","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1669","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=685;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=6b1207a7adeda7f0"} +{"_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25539768","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317018816640","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=686;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=ab2237e139eb965e","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.744648129Z\",\"ns\":\"ChainDB.LedgerEvent.Snapshot.TookSnapshot\",\"data\":{\"enclosedTime\":{\"tag\":\"RisingEdge\"},\"kind\":\"TookSnapshot\",\"snapshot\":{\"kind\":\"snapshot\"},\"tip\":\"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\"},\"sev\":\"Info\",\"thread\":\"24\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_PID":"759","__SEQNUM":"1670","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016"} +{"__SEQNUM":"1671","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=687;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=ebd4846d6594ddb6","PRIORITY":"6","_CAP_EFFECTIVE":"0","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"25539768","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317018816640","_COMM":"cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.76007076Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__SEQNUM":"1672","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018816640","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=688;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=c48e31e420f151c8","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","PRIORITY":"6","_HOSTNAME":"leios-node","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.760125515Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"25539768","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system"} +{"__MONOTONIC_TIMESTAMP":"25539768","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=689;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=c138014bd18c0b38","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.76019815Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"blockNo\":18,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":280},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018816640","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1673"} +{"_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317018816640","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.760414658Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":280},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68a;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=bb3b8798581e4491","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"25539768","__SEQNUM":"1674"} +{"_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1675","_HOSTNAME":"leios-node","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68b;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=bd86ae242b156482","_CAP_EFFECTIVE":"0","_PID":"759","PRIORITY":"6","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25539768","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317018816640","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.785008566Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018816640","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68c;b=082ebd52b7694299b9566558b64d809c;m=185b4b8;t=641e8933e5080;x=fc277f1ffcb2273c","__SEQNUM":"1676","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.785068909Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25539768","_PID":"759","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service"} +{"_GID":"10016","PRIORITY":"6","__SEQNUM":"1677","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68d;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=b4d6e0775af38586","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.834156712Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25668163","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317018945036","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node"} +{"_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68e;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=980a3244e6034835","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.869999256Z\",\"ns\":\"ChainDB.LedgerEvent.Snapshot.TookSnapshot\",\"data\":{\"enclosedTime\":{\"contents\":0.125330174,\"tag\":\"FallingEdgeWith\"},\"kind\":\"TookSnapshot\",\"snapshot\":{\"kind\":\"snapshot\"},\"tip\":\"RealPoint (SlotNo 52) 23b021f8e2c06e64b10647d9eeb5c9f11e50181f5a569424e49f2448f6d5f8a8\"},\"sev\":\"Info\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317018945036","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25668163","_UID":"10016","__SEQNUM":"1678","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=68f;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=eaea5f4610653835","__REALTIME_TIMESTAMP":"1761317018945036","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25668163","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.876574952Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"BlockPoint\",\"slot\":80},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"1679","_PID":"759","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","PRIORITY":"6","_COMM":"cardano-node","_UID":"10016","_TRANSPORT":"stdout"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:38.876789505Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":6,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":80,\"tieBreakVRF\":\"60c8ea183da592e4ab82f14e26da75c4763e9993021f45e4b9b927e161bf79fb3e0b7bf8b0dfd31ba874215ae82f4eeafe0a7f66f21df1d15e86ccc89943c02c\"},\"newtip\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80\",\"oldTipSelectView\":{\"chainLength\":5,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":77,\"tieBreakVRF\":\"eb8dc698abfd6a3394a29bb45182af6b8136999142a0b290e83cb92575a4f27f8aa8b27e08b0b32cad70ad57666b34a6e18e24408b20004fe8c7125889059d4e\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"25668163","_PID":"759","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=690;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=9524ca1100d158cc","PRIORITY":"6","__SEQNUM":"1680","__REALTIME_TIMESTAMP":"1761317018945036","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317018945036","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=691;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=cfc9e87fd17f756a","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM":"1681","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25668163","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913048862Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a@80\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317018945036","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25668163","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=692;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=fd0ed80faa7f59a5","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913158094Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__SEQNUM":"1682"} +{"PRIORITY":"6","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"25668163","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317018945036","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=693;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=7d878bb356e9320","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913185751Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"Point\",\"slot\":95},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_UID":"10016","_PID":"759","__SEQNUM":"1683","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913255592Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"Point\",\"slot\":95},\"blockNo\":\"7\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"25668163","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_PID":"759","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1684","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317018945036","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=694;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=5d81b1179634d027","_UID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=695;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=7564cad50132b04c","_TRANSPORT":"stdout","_UID":"10016","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.91351177Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"BlockPoint\",\"slot\":53},\"head\":{\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"BlockPoint\",\"slot\":80}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1685","__MONOTONIC_TIMESTAMP":"25668163","__REALTIME_TIMESTAMP":"1761317018945036","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1686","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317018945036","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=696;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=70fc4bf638dd0e","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913562335Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"Point\",\"slot\":95},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"25668163","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_UID":"10016","_HOSTNAME":"leios-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"25668163","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.927031924Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"Point\",\"slot\":247},\"kind\":\"AddedBlockToQueue\",\"queueSize\":10},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__SEQNUM":"1687","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317018945036","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=697;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=431251e0beaf89b","_RUNTIME_SCOPE":"system"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=698;b=082ebd52b7694299b9566558b64d809c;m=187aa43;t=641e89340460c;x=670dc193297fd15f","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.927190883Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317018945036","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1688","__MONOTONIC_TIMESTAMP":"25668163","PRIORITY":"6"} +{"__SEQNUM":"1689","_UID":"10016","_TRANSPORT":"stdout","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=699;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=2483164c9ebf1a22","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317019033578","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.913642792Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_FACILITY":"3","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"25756705","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1690","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"25756705","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.944000561Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019033578","SYSLOG_FACILITY":"3","_UID":"10016","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69a;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=2fa15b53fb0ebc3c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.981041302Z\",\"ns\":\"Net.InboundGovernor.Local.MuxCleanExit\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"MuxCleanExit\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1691","_RUNTIME_SCOPE":"system","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317019033578","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25756705","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69b;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=af3a121c83402378","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019033578","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__MONOTONIC_TIMESTAMP":"25756705","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_PID":"759","_COMM":"cardano-node","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__SEQNUM":"1692","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.981082928Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69c;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=a277c430d6cd25d","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25756705","__REALTIME_TIMESTAMP":"1761317019033578","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.981116731Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_PID":"759","__SEQNUM":"1693","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69d;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=57e8cd8eeec2a206","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_PID":"759","__MONOTONIC_TIMESTAMP":"25756705","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.98117875Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionCleanup\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@0\"},\"kind\":\"ConnectionCleanup\"},\"sev\":\"Debug\",\"thread\":\"76\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019033578","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1694","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69e;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=a3e8471b7b2e389","_COMM":"cardano-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=69f;b=082ebd52b7694299b9566558b64d809c;m=1890421;t=641e893419fea;x=92b6aac4dc32f774","_RUNTIME_SCOPE":"system","__SEQNUM":"1695","__REALTIME_TIMESTAMP":"1761317019033578","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__MONOTONIC_TIMESTAMP":"25756705","_COMM":"cardano-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:38.98125781Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":0,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"76\",\"host\":\"leios-node\"}"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.016633815Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"5ecd12b363657693f31e62421726fcc427788eed6d2fb22abad81a853120cf59\",\"kind\":\"BlockPoint\",\"slot\":53}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019073515","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a0;b=082ebd52b7694299b9566558b64d809c;m=189a024;t=641e893423beb;x=d211a2b9ce048c54","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__SEQNUM":"1696","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"25796644","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6"} +{"_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25796644","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019073515","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM":"1697","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.016706729Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":53}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_PID":"759","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a1;b=082ebd52b7694299b9566558b64d809c;m=189a024;t=641e893423beb;x=c59843b182fb49b1","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25796644","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM":"1698","__REALTIME_TIMESTAMP":"1761317019073515","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.038485754Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"BlockPoint\",\"slot\":95},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a2;b=082ebd52b7694299b9566558b64d809c;m=189a024;t=641e893423beb;x=d3f74abf12f6bc80","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__REALTIME_TIMESTAMP":"1761317019092475","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a3;b=082ebd52b7694299b9566558b64d809c;m=189ea35;t=641e8934285fb;x=ca5f2a90197d8d68","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:37.873347168 UTC to 2025-10-24 14:43:39.080407004 UTC","_UID":"10016","_COMM":"cardano-node","__SEQNUM":"1699","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"25815605","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"25820244","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.038657843Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":7,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":95,\"tieBreakVRF\":\"ab3d31c51247d9226d70612adaeab6b8888c21496bd1d46954b5c4d0e7a85d3f737682107aed5e46337a263a9d0ffedd650591a1a4699d99964d5d019a628fcb\"},\"newtip\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95\",\"oldTipSelectView\":{\"chainLength\":6,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":80,\"tieBreakVRF\":\"60c8ea183da592e4ab82f14e26da75c4763e9993021f45e4b9b927e161bf79fb3e0b7bf8b0dfd31ba874215ae82f4eeafe0a7f66f21df1d15e86ccc89943c02c\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a4;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=56bbbb70c2140e88","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__SEQNUM":"1700","__REALTIME_TIMESTAMP":"1761317019097117","_GID":"10016","_PID":"759"} +{"_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"25820244","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a5;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=aadb3299589bb78f","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.038828814Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068@95\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_PID":"759","_TRANSPORT":"stdout","_GID":"10016","_HOSTNAME":"leios-node","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317019097117","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1701","_SYSTEMD_UNIT":"cardano-node.service"} +{"__SEQNUM":"1702","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019097117","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a6;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=df3dc00e066d932d","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.043787824Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","__MONOTONIC_TIMESTAMP":"25820244","_PID":"759","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_FACILITY":"3"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317019097117","__MONOTONIC_TIMESTAMP":"25820244","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a7;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=a9c1c2f909318dea","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1703","_PID":"759","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.043817437Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"Point\",\"slot\":108},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a8;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=8e5d7e4bb9fef76a","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1704","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019097117","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.066760577Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"BlockPoint\",\"slot\":59},\"head\":{\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"BlockPoint\",\"slot\":95}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"25820244","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","PRIORITY":"6"} +{"__SEQNUM":"1705","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"25820244","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6a9;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=61fbd0f3bd501478","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.06681198Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"Point\",\"slot\":108},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019097117"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6aa;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=c631c11991f926bc","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019097117","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.080407004Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"25820244","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__SEQNUM":"1706","_COMM":"cardano-node","_GID":"10016","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.08046567Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019097117","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25820244","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ab;b=082ebd52b7694299b9566558b64d809c;m=189fc54;t=641e89342981d;x=b39025b5bb7fe34b","__SEQNUM":"1707","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ac;b=082ebd52b7694299b9566558b64d809c;m=18afe11;t=641e8934399da;x=c7a9c082ba3286a8","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.144666567Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"0341e8795f13d6bcbd0d1fec0fc03fb75ede8cd6d75999c19946f3bb2c0f434e\",\"kind\":\"BlockPoint\",\"slot\":59}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1708","_HOSTNAME":"leios-node","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019163098","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"25886225","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.145231723Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":59}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM":"1709","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ad;b=082ebd52b7694299b9566558b64d809c;m=18afe11;t=641e8934399da;x=f4a72f8876a273a5","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019163098","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_PID":"759","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"25886225","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"25907069","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ae;b=082ebd52b7694299b9566558b64d809c;m=18b4f7d;t=641e89343eb44;x=466348731be6d507","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM":"1710","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__REALTIME_TIMESTAMP":"1761317019183940","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.162756855Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"BlockPoint\",\"slot\":108},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.173558787Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":8,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":108,\"tieBreakVRF\":\"777fe4a1dbc02b8f3af99a70a3ad4a8b9b832c80c776cc42c111a88ded792943d288d4002b536a2b54fb68713a1b8fd24b4ae287336db737e8f52b91185642dd\"},\"newtip\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108\",\"oldTipSelectView\":{\"chainLength\":7,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":95,\"tieBreakVRF\":\"ab3d31c51247d9226d70612adaeab6b8888c21496bd1d46954b5c4d0e7a85d3f737682107aed5e46337a263a9d0ffedd650591a1a4699d99964d5d019a628fcb\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_UID":"10016","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"25907069","_HOSTNAME":"leios-node","__SEQNUM":"1711","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019183940","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6af;b=082ebd52b7694299b9566558b64d809c;m=18b4f7d;t=641e89343eb44;x=6a6645a88808b331","PRIORITY":"6","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1712","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.177589746Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908@108\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_UID":"10016","__MONOTONIC_TIMESTAMP":"25907069","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","PRIORITY":"6","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b0;b=082ebd52b7694299b9566558b64d809c;m=18b4f7d;t=641e89343eb44;x=eabef64324657a6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317019183940","_GID":"10016","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019183940","_PID":"759","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b1;b=082ebd52b7694299b9566558b64d809c;m=18b4f7d;t=641e89343eb44;x=79d975623c93d00c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.17877621Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"BlockPoint\",\"slot\":77}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"25907069","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1713","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.17882901Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":77}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b2;b=082ebd52b7694299b9566558b64d809c;m=18b4f7d;t=641e89343eb44;x=7fe9ad3d8516fefd","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019183940","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"25907069","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1714","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","PRIORITY":"6"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b3;b=082ebd52b7694299b9566558b64d809c;m=18be606;t=641e8934481cf;x=383906efdb68fdba","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_UID":"10016","_TRANSPORT":"stdout","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.179142458Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1715","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317019222479","__MONOTONIC_TIMESTAMP":"25945606","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM":"1716","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"25989401","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.179239397Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"Point\",\"slot\":111},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019266239","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b4;b=082ebd52b7694299b9566558b64d809c;m=18c9119;t=641e893452cbf;x=e73645e7ed782ffe"} +{"__MONOTONIC_TIMESTAMP":"25998291","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b5;b=082ebd52b7694299b9566558b64d809c;m=18cb3d3;t=641e893454f85;x=c37b4423fa0a300c","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.18016661Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"312446d47cbeb3861cdfea334a67aa9fa2b58e90b83fdb6b2d097a55f0b57a37\",\"kind\":\"BlockPoint\",\"slot\":77},\"head\":{\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"BlockPoint\",\"slot\":108}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1717","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019275141","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b6;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=24c59f5d623e641f","__MONOTONIC_TIMESTAMP":"26006323","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317019283196","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.180581747Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"Point\",\"slot\":111},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1718","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6"} +{"PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1719","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317019283196","__MONOTONIC_TIMESTAMP":"26006323","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b7;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=d1236b22feffd3ab","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.180737912Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016"} +{"_COMM":"cardano-node","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.180779816Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26006323","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b8;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=470aecae807ea5e2","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1720","_UID":"10016","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317019283196"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317019283196","__MONOTONIC_TIMESTAMP":"26006323","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6b9;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=744865b26d60b298","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.204282804Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":280},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_GID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system"} +{"__MONOTONIC_TIMESTAMP":"26006323","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.256793109Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ba;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=5f10013d2a076d7c","_CAP_EFFECTIVE":"0","__SEQNUM":"1722","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019283196","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__MONOTONIC_TIMESTAMP":"26006323","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019283196","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6bb;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=6ee309f603039f3c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","PRIORITY":"6","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.259512169Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":17,\"headerHash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1723","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1724","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6bc;b=082ebd52b7694299b9566558b64d809c;m=18cd333;t=641e893456efc;x=fd92c378c7b59f2c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"26006323","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.259645147Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317019283196","PRIORITY":"6"} +{"_CAP_EFFECTIVE":"0","__SEQNUM":"1725","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.259730353Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26050248","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019327121","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6bd;b=082ebd52b7694299b9566558b64d809c;m=18d7ec8;t=641e893461a91;x=fe9a2a0ccdf4b4f","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1726","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.259827573Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"blockNo\":19,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":304},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6be;b=082ebd52b7694299b9566558b64d809c;m=18d7ec8;t=641e893461a91;x=13dc3b208fa2f5","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317019327121","__MONOTONIC_TIMESTAMP":"26050248","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.261247585Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"BlockPoint\",\"slot\":111},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1727","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_PID":"759","__MONOTONIC_TIMESTAMP":"26050248","__REALTIME_TIMESTAMP":"1761317019327121","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6bf;b=082ebd52b7694299b9566558b64d809c;m=18d7ec8;t=641e893461a91;x=db3ba42f53aeee31"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.261476944Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":9,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":111,\"tieBreakVRF\":\"8c17f38d81c6b0034252dd6f25e3ac067ff125e02496ea7f015a659e2fc4065a982be63b4bbaf60189335d7ac21cf07403c99bcda277ac2a05c4a784905b5885\"},\"newtip\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111\",\"oldTipSelectView\":{\"chainLength\":8,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":108,\"tieBreakVRF\":\"777fe4a1dbc02b8f3af99a70a3ad4a8b9b832c80c776cc42c111a88ded792943d288d4002b536a2b54fb68713a1b8fd24b4ae287336db737e8f52b91185642dd\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019327121","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c0;b=082ebd52b7694299b9566558b64d809c;m=18d7ec8;t=641e893461a91;x=ca1d4c16bb7a5f00","SYSLOG_FACILITY":"3","__SEQNUM":"1728","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"26050248","_COMM":"cardano-node"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.261642608Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828@111\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1729","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26050248","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_UID":"10016","_PID":"759","_HOSTNAME":"leios-node","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c1;b=082ebd52b7694299b9566558b64d809c;m=18d7ec8;t=641e893461a91;x=ade333b2523a4f","__REALTIME_TIMESTAMP":"1761317019327121","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c2;b=082ebd52b7694299b9566558b64d809c;m=18e1037;t=641e89346ac00;x=40fcbcef8b003568","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.261765528Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019364352","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1730","__MONOTONIC_TIMESTAMP":"26087479","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","PRIORITY":"6","_UID":"10016"} +{"_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM":"1731","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317019364352","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.261806316Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"Point\",\"slot\":148},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__MONOTONIC_TIMESTAMP":"26087479","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c3;b=082ebd52b7694299b9566558b64d809c;m=18e1037;t=641e89346ac00;x=d277a886e35140ab","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_UID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"26087479","__REALTIME_TIMESTAMP":"1761317019364352","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1732","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c4;b=082ebd52b7694299b9566558b64d809c;m=18e1037;t=641e89346ac00;x=a0d8c49c94591d45","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.26541711Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.282408375Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":304},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_UID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317019364352","__MONOTONIC_TIMESTAMP":"26087479","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1733","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c5;b=082ebd52b7694299b9566558b64d809c;m=18e1037;t=641e89346ac00;x=d51b7112619cf302","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__SEQNUM":"1734","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.318978386Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019386210","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"26109337","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c6;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=78b1536b904b64ff","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"26109337","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.319048786Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019386210","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c7;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=4998fe3b87699fcd","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__SEQNUM":"1735"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.325022451Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"BlockPoint\",\"slot\":80}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__MONOTONIC_TIMESTAMP":"26109337","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c8;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=103928a5ee2dc98b","__SEQNUM":"1736","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019386210","_GID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019386210","SYSLOG_FACILITY":"3","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26109337","_COMM":"cardano-node","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1737","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.32507134Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":80}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6c9;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=4580ff7968cde52f"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.326133206Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"b69dee53a6792b9f66b7a13f613b55ce0db374b1f01fb76908275d380049305a\",\"kind\":\"BlockPoint\",\"slot\":80},\"head\":{\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"BlockPoint\",\"slot\":111}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26109337","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_PID":"759","__SEQNUM":"1738","_RUNTIME_SCOPE":"system","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019386210","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ca;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=d8ec6dc83f48cb51"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"26109337","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019386210","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.326204444Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"Point\",\"slot\":148},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6cb;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=207dc16661a4d22b","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1739","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26109337","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6cc;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=83412ad9e5597751","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.326261435Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"1740","_PID":"759","__REALTIME_TIMESTAMP":"1761317019386210","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_UID":"10016"} +{"_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.32628099Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019386210","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1741","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26109337","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6cd;b=082ebd52b7694299b9566558b64d809c;m=18e6599;t=641e893470162;x=39709ee0f0be7ac3","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1742","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ce;b=082ebd52b7694299b9566558b64d809c;m=18f2423;t=641e89347bfea;x=b3a9177685b66aa6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26158115","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_UID":"10016","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.384173264Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":186581520,\"CentiBlkIO\":0,\"CentiCpu\":84,\"CentiGC\":2,\"CentiMut\":75,\"FsRd\":50814976,\"FsWr\":69632,\"GcsMajor\":2,\"GcsMinor\":4,\"Heap\":49283072,\"Live\":3540008,\"NetRd\":0,\"NetWr\":0,\"RSS\":98697216,\"Threads\":11,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019434986"} +{"_GID":"10016","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019442073","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6cf;b=082ebd52b7694299b9566558b64d809c;m=18f3fd2;t=641e89347db99;x=c904b14fe2747d7","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1743","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.385492147Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"BlockPoint\",\"slot\":148},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26165202","SYSLOG_FACILITY":"3"} +{"_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d0;b=082ebd52b7694299b9566558b64d809c;m=18f3fd2;t=641e89347db99;x=a8ac4a5100fa3a3b","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019442073","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.385683233Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0@148\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_HOSTNAME":"leios-node","_PID":"759","_RUNTIME_SCOPE":"system","__SEQNUM":"1744","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"26165202"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.385777658Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019442073","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__MONOTONIC_TIMESTAMP":"26165202","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d1;b=082ebd52b7694299b9566558b64d809c;m=18f3fd2;t=641e89347db99;x=e6989f58e092ded","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1745","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d2;b=082ebd52b7694299b9566558b64d809c;m=18f3fd2;t=641e89347db99;x=1b4efbaff74d02c5","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.385801963Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"Point\",\"slot\":162},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317019442073","_PID":"759","_RUNTIME_SCOPE":"system","_UID":"10016","_HOSTNAME":"leios-node","_GID":"10016","PRIORITY":"6","__SEQNUM":"1746","__MONOTONIC_TIMESTAMP":"26165202","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d3;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=d71127896bd8258f","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.406700429Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":304},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_TRANSPORT":"stdout","_UID":"10016","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1747","__MONOTONIC_TIMESTAMP":"26191290","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317019468161","_SYSTEMD_SLICE":"system.slice","_GID":"10016"} +{"PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d4;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=596230ce9269df90","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM":"1748","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26191290","_UID":"10016","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.441975304Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"Point\",\"slot\":162},\"blockNo\":\"11\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019468161","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_GID":"10016"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.452427191Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"BlockPoint\",\"slot\":95},\"head\":{\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"BlockPoint\",\"slot\":148}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","__REALTIME_TIMESTAMP":"1761317019468161","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1749","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"26191290","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d5;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=9e8cacdae54c3da3","_UID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_GID":"10016","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_UID":"10016","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d6;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=9f03f9ea41e95588","__SEQNUM":"1750","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019468161","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26191290","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.452484181Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"Point\",\"slot\":162},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_PID":"759","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node"} +{"_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1751","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d7;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=cdf3a4bde003db73","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__MONOTONIC_TIMESTAMP":"26191290","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.452557654Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019468161","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317019468161","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"26191290","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d8;b=082ebd52b7694299b9566558b64d809c;m=18fa5ba;t=641e893484181;x=e9967d5010df66ce","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.452579445Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1752","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019512398","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6d9;b=082ebd52b7694299b9566558b64d809c;m=1905288;t=641e89348ee4e;x=30166e1411c1ebb6","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1753","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.475404413Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"f0c284a84d8c6276f539e61a688979d89b544d817cb75f704d2c5fa838996068\",\"kind\":\"BlockPoint\",\"slot\":95}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26235528"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26235528","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.475465594Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":95}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_GID":"10016","_HOSTNAME":"leios-node","__SEQNUM":"1754","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6da;b=082ebd52b7694299b9566558b64d809c;m=1905288;t=641e89348ee4e;x=eeefeca454b84064","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019512398"} +{"PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26250187","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019527060","__SEQNUM":"1755","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6db;b=082ebd52b7694299b9566558b64d809c;m=1908bcb;t=641e893492794;x=4fd777dd3c6404da","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.502435222Z\",\"ns\":\"Net.PeerSelection.Selection.ChurnWait\",\"data\":{\"diffTime\":912.920456380641,\"kind\":\"ChurnWait\"},\"sev\":\"Info\",\"thread\":\"56\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__REALTIME_TIMESTAMP":"1761317019527060","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.512327541Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"BlockPoint\",\"slot\":162},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1756","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__MONOTONIC_TIMESTAMP":"26250187","_UID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6dc;b=082ebd52b7694299b9566558b64d809c;m=1908bcb;t=641e893492794;x=908018c929e6e7fb","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.52582339Z\",\"ns\":\"Net.PeerSelection.Selection.TargetsChanged\",\"data\":{\"current\":{\"kind\":\"PeerSelectionTargets\",\"targetActiveBigLedgerPeers\":5,\"targetActivePeers\":15,\"targetEstablishedBigLedgerPeers\":10,\"targetEstablishedPeers\":40,\"targetKnownBigLedgerPeers\":15,\"targetKnownPeers\":150,\"targetRootPeers\":60},\"kind\":\"TargetsChanged\",\"previous\":{\"kind\":\"PeerSelectionTargets\",\"targetActiveBigLedgerPeers\":5,\"targetActivePeers\":15,\"targetEstablishedBigLedgerPeers\":10,\"targetEstablishedPeers\":40,\"targetKnownBigLedgerPeers\":15,\"targetKnownPeers\":150,\"targetRootPeers\":0}},\"sev\":\"Notice\",\"thread\":\"54\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","PRIORITY":"6","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__SEQNUM":"1757","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6dd;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=8fc66352c81cab9e","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019546933","_PID":"759","__MONOTONIC_TIMESTAMP":"26270062","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016"} +{"_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6de;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=d23c3f54249175e4","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526022298Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersRequest\",\"data\":{\"kind\":\"BigLedgerPeersRequest\",\"numberOfBigLedgerPeers\":0,\"targetNumberOfBigLedgerPeers\":15},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019546933","_UID":"10016","_PID":"759","__SEQNUM":"1758","__MONOTONIC_TIMESTAMP":"26270062","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019546933","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526093536Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6df;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=fd2e8967b144d8a2","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_UID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26270062","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice"} +{"__SEQNUM":"1760","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e0;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=17affeb6612ad144","__MONOTONIC_TIMESTAMP":"26270062","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526291048Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"Point\",\"slot\":280},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019546933","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e1;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=2416f63be2390d86","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1761","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26270062","_UID":"10016","_PID":"759","__REALTIME_TIMESTAMP":"1761317019546933","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526374578Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"delay\":1364125.526191594,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":863},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e2;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=a5cc682b1bf1b985","_PID":"759","__MONOTONIC_TIMESTAMP":"26270062","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526430451Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019546933","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_COMM":"cardano-node","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1762","PRIORITY":"6","_UID":"10016"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_PID":"759","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526460343Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317019546933","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e3;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=3e2e7ae74814ca04","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM":"1763","_COMM":"cardano-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26270062","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e4;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=92d881c8dbbccf23","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019546933","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26270062","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526540521Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":18,\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_GID":"10016","__SEQNUM":"1764","_UID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"_CAP_EFFECTIVE":"0","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019546933","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526566781Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26270062","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e5;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=d24e06e55b35638f","_COMM":"cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"1765","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_GID":"10016"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26270062","_GID":"10016","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__SEQNUM":"1766","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e6;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=18c526f26f5589a","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526591365Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019546933"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e7;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=3bdc8ea012cd1a4b","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"26270062","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.526630476Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"blockNo\":20,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":325},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1767","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019546933","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_SLICE":"system.slice","_UID":"10016","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.540149792Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a@162\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e8;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=c4fb9bc400544a4b","_PID":"759","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1768","__MONOTONIC_TIMESTAMP":"26270062","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317019546933","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__MONOTONIC_TIMESTAMP":"26270062","_GID":"10016","__SEQNUM":"1769","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6e9;b=082ebd52b7694299b9566558b64d809c;m=190d96e;t=641e893497535;x=56dca68e7d30fdfe","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317019546933","_SYSTEMD_SLICE":"system.slice","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.540279697Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1770","_UID":"10016","_GID":"10016","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ea;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=a1d172bc7fbea8b0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26347502","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019624373","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.540306237Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"Point\",\"slot\":179},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"__MONOTONIC_TIMESTAMP":"26347502","__SEQNUM":"1771","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019624373","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6eb;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=42282e26e98a41e5","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.541117513Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_CAP_EFFECTIVE":"0"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.541525386Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ec;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=6e10415b675f25f","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1772","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26347502","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019624373","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ed;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=1578b025afb24eb2","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM":"1773","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317019624373","__MONOTONIC_TIMESTAMP":"26347502","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.541570643Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_PID":"759","_HOSTNAME":"leios-node"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1774","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317019624373","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.541786592Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"BlockPoint\",\"slot\":108},\"head\":{\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"BlockPoint\",\"slot\":162}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ee;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=b4cf84955f8e161a","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26347502","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_COMM":"cardano-node"} +{"_UID":"10016","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ef;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=2d7ec827ae19748","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26347502","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019624373","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1775","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.541829056Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"Point\",\"slot\":179},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node"} +{"_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26347502","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.542390021Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f0;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=1130e552b99deb96","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__SEQNUM":"1776","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019624373","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1777","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019624373","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_PID":"759","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"26347502","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.542462377Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":19,\"headerHash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f1;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=43ddd1165461ed8a"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019624373","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.542491431Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26347502","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f2;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=371f68121776add5","__SEQNUM":"1778","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_PID":"759"} +{"_CAP_EFFECTIVE":"0","PRIORITY":"6","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1779","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"26347502","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.542516573Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019624373","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f3;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=442551fe953cab7d","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_RUNTIME_SCOPE":"system"} +{"__SEQNUM":"1780","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019624373","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.542555964Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"blockNo\":21,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":333},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26347502","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f4;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=cdbd59806cd70df5","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","SYSLOG_FACILITY":"3","PRIORITY":"6","_COMM":"cardano-node","__SEQNUM":"1781","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f5;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=3805af29f37a4f52","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26347502","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.543963685Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019624373","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317019624373","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1782","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f6;b=082ebd52b7694299b9566558b64d809c;m=19207ee;t=641e8934aa3b5;x=75dab5bb0ef0ef18","_CAP_EFFECTIVE":"0","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.543999164Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26347502"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019704972","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_UID":"10016","PRIORITY":"6","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26428104","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1783","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.544620752Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f7;b=082ebd52b7694299b9566558b64d809c;m=19342c8;t=641e8934bde8c;x=c636058367cff55"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019711083","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"26434210","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.545760841Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"BlockPoint\",\"slot\":179},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_GID":"10016","__SEQNUM":"1784","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f8;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=f8c8adcf37f9b034","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__SEQNUM":"1785","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.562129401Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsRequest\",\"data\":{\"kind\":\"PublicRootsRequest\",\"numberOfRootPeers\":1,\"targetNumberOfRootPeers\":60},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6f9;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=fdd6d409a0c17401","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"26434210","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019711083","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317019711083","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","__MONOTONIC_TIMESTAMP":"26434210","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.573158177Z\",\"ns\":\"Net.Server.Local.AcceptConnection\",\"data\":{\"address\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"AcceptConnection\"},\"sev\":\"Debug\",\"thread\":\"48\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1786","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6fa;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=ef1d617c46d085e"} +{"PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1787","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26434210","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6fb;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=9cecec885cc418f8","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019711083","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.573226622Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0"} +{"_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019711083","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26434210","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1788","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.573250927Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":15},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6fc;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=446cb40dc8e98f52","_UID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM":"1789","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.57328473Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":26.296387979,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26434210","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6fd;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=2f3221a1feae2277","_GID":"10016","_COMM":"cardano-node","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019711083","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_UID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__MONOTONIC_TIMESTAMP":"26434210","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317019711083","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6fe;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=cac52551cab4b52","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1790","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.573309314Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}"} +{"_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__SEQNUM":"1791","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019711083","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.573362673Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"83\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26434210","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_GID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=6ff;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=72ff970b2e8b6716","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__REALTIME_TIMESTAMP":"1761317019711083","PRIORITY":"6","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.591434802Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=700;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=79e9d956a11a5cb6","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"26434210","__SEQNUM":"1792","_GID":"10016","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__REALTIME_TIMESTAMP":"1761317019711083","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_PID":"759","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1793","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","PRIORITY":"6","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.591544872Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=701;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=25954e47ed4bd17a","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26434210","_UID":"10016","_RUNTIME_SCOPE":"system"} +{"_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1794","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.615499872Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709@179\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019711083","_GID":"10016","__MONOTONIC_TIMESTAMP":"26434210","_TRANSPORT":"stdout","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=702;b=082ebd52b7694299b9566558b64d809c;m=1935aa2;t=641e8934bf66b;x=ccb0b2a04c293383","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=703;b=082ebd52b7694299b9566558b64d809c;m=19429fe;t=641e8934cc5c5;x=1e55e2fb403e4fe5","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26487294","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317019764165","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_TRANSPORT":"stdout","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1795","SYSLOG_FACILITY":"3","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.615581446Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26493088","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=704;b=082ebd52b7694299b9566558b64d809c;m=19440a0;t=641e8934cdc64;x=abd177864a4561d7","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.615607148Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"Point\",\"slot\":183},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"1796","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019769956","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26493088","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019769956","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=705;b=082ebd52b7694299b9566558b64d809c;m=19440a0;t=641e8934cdc64;x=572dbfb2740c2254","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.634235214Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM":"1797","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice"} +{"_CAP_EFFECTIVE":"0","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1798","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.634340814Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":20,\"headerHash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=706;b=082ebd52b7694299b9566558b64d809c;m=19440a0;t=641e8934cdc64;x=98f586825cab1ee4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019769956","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"26493088","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_GID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=707;b=082ebd52b7694299b9566558b64d809c;m=19440a0;t=641e8934cdc64;x=d29004863a66a822","_PID":"759","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26493088","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.634372941Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019769956","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1799","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=708;b=082ebd52b7694299b9566558b64d809c;m=194a22f;t=641e8934d3df6;x=485030f01fa0bf22","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__SEQNUM":"1800","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"26518063","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:39.08046567 UTC to 2025-10-24 14:43:39.793785659 UTC","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_PID":"759","__REALTIME_TIMESTAMP":"1761317019794934","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1801","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26523463","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.634398363Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019800330","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=709;b=082ebd52b7694299b9566558b64d809c;m=194b747;t=641e8934d530a;x=ed721b7128a07a58","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_COMM":"cardano-node","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system"} +{"_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1802","PRIORITY":"6","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"26529687","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317019806556","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70a;b=082ebd52b7694299b9566558b64d809c;m=194cf97;t=641e8934d6b5c;x=af788d9a74c99288","_COMM":"cardano-node","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.634439988Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"blockNo\":22,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":351},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_PID":"759","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26535330","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317019812199","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1803","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70b;b=082ebd52b7694299b9566558b64d809c;m=194e5a2;t=641e8934d8167;x=7a6f74a74009b850","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.6734916Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"83\",\"host\":\"leios-node\"}"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019817281","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26540409","_RUNTIME_SCOPE":"system","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70c;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=a68fd86d5be9c17d","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.678696451Z\",\"ns\":\"Net.ConnectionManager.Local.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Inbound\",\"remoteAddress\":{\"path\":\"/run/cardano-node/node.socket@1\"}},\"sev\":\"Debug\",\"thread\":\"84\",\"host\":\"leios-node\"}","__SEQNUM":"1804","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_GID":"10016","_HOSTNAME":"leios-node"} +{"_GID":"10016","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70d;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=8776f9b41ecf51be","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.683496502Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","__SEQNUM":"1805","_COMM":"cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26540409","__REALTIME_TIMESTAMP":"1761317019817281","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759"} +{"_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26540409","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019817281","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.683516337Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":59},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__SEQNUM":"1806","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70e;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=359b37dcac787118","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM":"1807","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_PID":"759","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26540409","__REALTIME_TIMESTAMP":"1761317019817281","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.68353701Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":26.406647244,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=70f;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=9f2ba4ffdbb2dee6","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.683550699Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26540409","_GID":"10016","_COMM":"cardano-node","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM":"1808","__REALTIME_TIMESTAMP":"1761317019817281","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=710;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=b768a90c050356d7","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1809","_UID":"10016","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019817281","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.683729772Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"b986a9094715f0af0e75c4de4d933bdefe863516a925c34c7b21c756afaee908\",\"kind\":\"BlockPoint\",\"slot\":108}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26540409","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=711;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=635d48a8ed7153fe","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1810","__MONOTONIC_TIMESTAMP":"26540409","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.697517279Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019817281","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=712;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=d6f071a84b7d808f","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016"} +{"SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__SEQNUM":"1811","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.697822904Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"BlockPoint\",\"slot\":111},\"head\":{\"headerHash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"BlockPoint\",\"slot\":179}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317019817281","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26540409","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=713;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=faeccfc0d6e82c5","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=714;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=eb76b0c3aafe85d7","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26540409","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.703720861Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"8a9fdda3ad8ef671272317791171c49b42df01a53f417c22dd24a52bdcabd828\",\"kind\":\"BlockPoint\",\"slot\":111}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM":"1812","__REALTIME_TIMESTAMP":"1761317019817281","_RUNTIME_SCOPE":"system"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=715;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=6be4dbaeb56aced7","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317019817281","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_PID":"759","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.703766397Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":111}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26540409","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","__SEQNUM":"1813"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1814","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=716;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=12f112cfdb882d2a","SYSLOG_FACILITY":"3","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.697924873Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"Point\",\"slot\":183},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26540409","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019817281","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice"} +{"SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=717;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=370372da1cc62bfc","_PID":"759","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26540409","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1815","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.70404688Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019817281","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_COMM":"cardano-node","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019817281","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=718;b=082ebd52b7694299b9566558b64d809c;m=194f979;t=641e8934d9541;x=f5fa63d10331bf59","_GID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.704068391Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"26540409","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1816","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"26612891","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317019889764","__SEQNUM":"1817","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=719;b=082ebd52b7694299b9566558b64d809c;m=196149b;t=641e8934eb064;x=465ecc6ce8863bc9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_UID":"10016","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.704097724Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.704125381Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019889764","__MONOTONIC_TIMESTAMP":"26612891","__SEQNUM":"1818","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71a;b=082ebd52b7694299b9566558b64d809c;m=196149b;t=641e8934eb064;x=d52b76a18874be82","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016"} +{"_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71b;b=082ebd52b7694299b9566558b64d809c;m=196149b;t=641e8934eb064;x=30f7e22cf66ac3b1","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1819","__REALTIME_TIMESTAMP":"1761317019889764","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.728735213Z\",\"ns\":\"Net.Handshake.Local.Receive.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@1\\\"}\",\"event\":\"Recv AnyMessage MsgProposeVersions (fromList [(NodeToClientV_16,TList [TInt 42,TBool False]),(NodeToClientV_17,TList [TInt 42,TBool False]),(NodeToClientV_18,TList [TInt 42,TBool False]),(NodeToClientV_19,TList [TInt 42,TBool False]),(NodeToClientV_20,TList [TInt 42,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"85\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_GID":"10016","_COMM":"cardano-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"26612891"} +{"SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019889764","__SEQNUM":"1820","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71c;b=082ebd52b7694299b9566558b64d809c;m=196149b;t=641e8934eb064;x=c06651140c13afdf","_CAP_EFFECTIVE":"0","_GID":"10016","__MONOTONIC_TIMESTAMP":"26612891","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.734037842Z\",\"ns\":\"Net.Handshake.Local.Send.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@1\\\"}\",\"event\":\"Send AnyMessage MsgAcceptVersion NodeToClientV_20 (TList [TInt 42,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"85\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6"} +{"_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71d;b=082ebd52b7694299b9566558b64d809c;m=196149b;t=641e8934eb064;x=ea06ac88a851c8f1","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1821","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26612891","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019889764","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.734070528Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"networkMagic\":42,\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":20},\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"85\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1822","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71e;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=cb3fb1db0aa662f","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.734123887Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"84\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_FACILITY":"3","_GID":"10016","__REALTIME_TIMESTAMP":"1761317019926617","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019926617","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=71f;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=ee457827963b64bb","SYSLOG_FACILITY":"3","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1823","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.734146515Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"84\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26649744"} +{"PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1824","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.741530694Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019926617","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=720;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=435c8cca06328138"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019926617","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.75565707Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"82\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=721;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=ae23fd859426672b","__SEQNUM":"1825","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1826","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.763527065Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317019926617","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=722;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=ab380e924429d3b3","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26649744","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_COMM":"cardano-node","PRIORITY":"6"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_TRANSPORT":"stdout","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__MONOTONIC_TIMESTAMP":"26649744","SYSLOG_FACILITY":"3","__SEQNUM":"1827","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.763836043Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317019926617","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=723;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=9008cbf493194041"} +{"_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.769358812Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"BlockPoint\",\"slot\":183},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317019926617","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=724;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=f37cf49294d8cd6e","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26649744","_PID":"759","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_RUNTIME_SCOPE":"system","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1828"} +{"_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317019926617","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.781712896Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd@183\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1829","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=725;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=1412aac5bfd4ec0a","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.781815423Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26649744","__SEQNUM":"1830","_COMM":"cardano-node","_UID":"10016","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=726;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=7b383ce53d4f2c96","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317019926617","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26649744","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.781839728Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"Point\",\"slot\":187},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317019926617","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM":"1831","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=727;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=dccbfaeef5e991e0","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.787625659Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"82\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__MONOTONIC_TIMESTAMP":"26649744","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=728;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=98956ac90057779f","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317019926617","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1832","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016"} +{"_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317019926617","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1833","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.79279084Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=729;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=78d7ca264a1e03e5","_COMM":"cardano-node","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","PRIORITY":"6","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_UID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72a;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=a13e4e4483c63cc5","__SEQNUM":"1834","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.793748504Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":21,\"headerHash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26649744","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317019926617","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1835","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72b;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=968b384aae0e2193","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.793785659Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317019926617","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice"} +{"_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72c;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=324d4cbc9c11ee54","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.794241863Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317019926617","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"26649744","__SEQNUM":"1836"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1837","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.794298574Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_PID":"759","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72d;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=2974087bc843524d","__REALTIME_TIMESTAMP":"1761317019926617","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26649744","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"26649744","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72e;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=d82d04d2f8be832d","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1838","_SYSTEMD_SLICE":"system.slice","_PID":"759","_HOSTNAME":"leios-node","_COMM":"cardano-node","_UID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317019926617","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.794520669Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service"} +{"_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317019926617","__SEQNUM":"1839","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=72f;b=082ebd52b7694299b9566558b64d809c;m=196a490;t=641e8934f4059;x=77541ef66d5218c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.79381192Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"26649744","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout"} +{"_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__SEQNUM":"1840","__REALTIME_TIMESTAMP":"1761317020016936","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=730;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=6acbae1a7ab7234d","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.794800593Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"blockNo\":23,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":357},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"26740063"} +{"_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.805359197Z\",\"ns\":\"Net.InboundGovernor.Local.NewConnection\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"NewConnection\",\"provenance\":\"Inbound\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"26740063","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317020016936","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM":"1841","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=731;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=25d40097e1990949","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.805439096Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1842","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__REALTIME_TIMESTAMP":"1761317020016936","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=732;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=6dde41692e27369b","__MONOTONIC_TIMESTAMP":"26740063","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__SEQNUM":"1843","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=733;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=2cf44cb0055d427f","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020016936","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.80547234Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26740063","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1844","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317020016936","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.834213982Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=734;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=3c67ff37967eb6b2","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26740063","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_PID":"759","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.846855253Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"BlockPoint\",\"slot\":148},\"head\":{\"headerHash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"BlockPoint\",\"slot\":183}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020016936","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=735;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=39d5545bd2179624","__MONOTONIC_TIMESTAMP":"26740063","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1845","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_COMM":"cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=736;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=f678fdbe57955137","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.86912652Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersResults\",\"data\":{\"diffTime\":4,\"group\":2,\"kind\":\"BigLedgerPeersResults\",\"result\":[]},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26740063","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM":"1846","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020016936","PRIORITY":"6"} +{"_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"26740063","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=737;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=42992c8b5f999b25","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM":"1847","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.869269275Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsResults\",\"data\":{\"diffTime\":2,\"group\":1,\"kind\":\"PublicRootsResults\",\"result\":{\"bigLedgerPeers\":[],\"bootstrapPeers\":[],\"kind\":\"PublicRootPeers\",\"ledgerPeers\":[],\"publicConfigPeers\":[]}},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020016936","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_UID":"10016"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=738;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=79e8d08d9a77ddc1","_PID":"759","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910316671Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"Point\",\"slot\":187},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"26740063","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__SEQNUM":"1848","__REALTIME_TIMESTAMP":"1761317020016936","_COMM":"cardano-node","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910388747Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020016936","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=739;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=6d241cb0c14e5e67","_UID":"10016","__MONOTONIC_TIMESTAMP":"26740063","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1849","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__SEQNUM":"1850","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020016936","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73a;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=913adb08716d3efa","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.91040942Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__MONOTONIC_TIMESTAMP":"26740063","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26740063","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910459706Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73b;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=a3b5b674805479b2","__REALTIME_TIMESTAMP":"1761317020016936","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1851","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73c;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=6c11f1908f98466b","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26740063","__REALTIME_TIMESTAMP":"1761317020016936","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","__SEQNUM":"1852","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910476747Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToWarmRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"PromotedToWarmRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundIdleSt\"}}},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","PRIORITY":"6","_GID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910496023Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":1},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26740063","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1853","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020016936","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73d;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=42436da55d36383a","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"__SEQNUM":"1854","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020016936","_GID":"10016","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73e;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=43b34a761d1c9d82","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910518093Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"RemoteWarmSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"26740063","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM":"1855","__REALTIME_TIMESTAMP":"1761317020016936","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910573687Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToHotRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"PromotedToHotRemote\"},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=73f;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=886732b817c80020","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26740063"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"26740063","PRIORITY":"6","_CAP_EFFECTIVE":"0","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910590728Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":1,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1856","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=740;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=6a689da16c1922bf","__REALTIME_TIMESTAMP":"1761317020016936","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=741;b=082ebd52b7694299b9566558b64d809c;m=198055f;t=641e89350a128;x=3c33e37416ac35dd","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"26740063","_PID":"759","__SEQNUM":"1857","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910604696Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"RemoteHotSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020016936","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_UID":"10016","__SEQNUM":"1858","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=742;b=082ebd52b7694299b9566558b64d809c;m=19998cf;t=641e893523498;x=b2ac23778f5289b9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020120216","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.91069996Z\",\"ns\":\"StateQueryServer.Receive.Acquire\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgAcquire\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"26843343","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26843343","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=743;b=082ebd52b7694299b9566558b64d809c;m=19998cf;t=641e893523498;x=c8e97308bf3d644c","_GID":"10016","__REALTIME_TIMESTAMP":"1761317020120216","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1859","_PID":"759","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.91079215Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=744;b=082ebd52b7694299b9566558b64d809c;m=199cd99;t=641e89352695e;x=86922880e508fef3","PRIORITY":"6","_COMM":"cardano-node","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.910824277Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM":"1860","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26856857","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020133726"} +{"_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020142154","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.931404267Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"b0c2dd73fefde5e9c31545c221f61efb01d7a41bfec697779cf132296f4469d0\",\"kind\":\"BlockPoint\",\"slot\":148}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26865283","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=745;b=082ebd52b7694299b9566558b64d809c;m=199ee83;t=641e893528a4a;x=6e3dde7a9050324a","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM":"1861","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_PID":"759"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.931449804Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":148}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__REALTIME_TIMESTAMP":"1761317020149932","_CAP_EFFECTIVE":"0","__SEQNUM":"1862","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26873060","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=746;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=f1fd521fd2799396","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout"} +{"_HOSTNAME":"leios-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020149932","__SEQNUM":"1863","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=747;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=bb2421460f21cf66","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_GID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"26873060","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.976068324Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_COMM":"cardano-node","_GID":"10016","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1864","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020149932","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=748;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=27e7b2eed9d813b8","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"26873060","_TRANSPORT":"stdout","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.976227003Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":22,\"headerHash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.976276171Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","PRIORITY":"6","_RUNTIME_SCOPE":"system","_UID":"10016","__MONOTONIC_TIMESTAMP":"26873060","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=749;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=5c9bb0ba8453b13b","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317020149932","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1865"} +{"__SEQNUM":"1866","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.976314165Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74a;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=482b486623e5f6dc","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"26873060","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020149932","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","PRIORITY":"6"} +{"__REALTIME_TIMESTAMP":"1761317020149932","MESSAGE":"{\"at\":\"2025-10-24T14:43:39.976375625Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"blockNo\":24,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":362},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1867","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74b;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=29826fa63e78b4c0","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26873060","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__REALTIME_TIMESTAMP":"1761317020149932","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.011442652Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74c;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=1f7ca30f196a3ddb","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__SEQNUM":"1868","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26873060","_TRANSPORT":"stdout","_PID":"759","PRIORITY":"6"} +{"_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_PID":"759","_GID":"10016","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.011697712Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74d;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=2ce2c6a9013e25db","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020149932","__SEQNUM":"1869","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"26873060"} +{"_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1870","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.011740455Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74e;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=423e109b4db3fcfe","PRIORITY":"6","_TRANSPORT":"stdout","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317020149932","__MONOTONIC_TIMESTAMP":"26873060","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=74f;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=5fbb4516ffb9e70e","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.028249816Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"BlockPoint\",\"slot\":187},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_PID":"759","__MONOTONIC_TIMESTAMP":"26873060","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317020149932","__SEQNUM":"1871","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=750;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=8dc3915f1345026e","_UID":"10016","_PID":"759","__SEQNUM":"1872","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26873060","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317020149932","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.028423861Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11@187\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_COMM":"cardano-node"} +{"_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1873","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.028499848Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26873060","_UID":"10016","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=751;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=a5f1c0dd76505419","_TRANSPORT":"stdout","_PID":"759","__REALTIME_TIMESTAMP":"1761317020149932","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26873060","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317020149932","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=752;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=ab5bb8ba224fe550","__SEQNUM":"1874","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.028523873Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"Point\",\"slot\":188},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_PID":"759","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020149932","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM":"1875","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=753;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=5c316439d674116f","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.028584216Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"Point\",\"slot\":188},\"blockNo\":\"15\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"26873060","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node"} +{"_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1876","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020149932","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.011922881Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=754;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=bf555ffa1868c6a2","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"26873060","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020149932","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"26873060","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=755;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=195b479e6ac3a823","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.098745368Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"BlockPoint\",\"slot\":162},\"head\":{\"headerHash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"BlockPoint\",\"slot\":187}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__SEQNUM":"1877","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016"} +{"_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26873060","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.098788669Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"Point\",\"slot\":188},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=756;b=082ebd52b7694299b9566558b64d809c;m=19a0ce4;t=641e89352a8ac;x=9963071eecaa974e","PRIORITY":"6","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020149932","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM":"1878"} +{"_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020250058","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=757;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=2e916c8701cdb856","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.098842587Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26973185","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__SEQNUM":"1879","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3"} +{"_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020250058","__SEQNUM":"1880","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=758;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=39a49dd98097bb7f","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"26973185","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.098861304Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__REALTIME_TIMESTAMP":"1761317020250058","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=759;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=4c12231555f58f40","__SEQNUM":"1881","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.11957092Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"26973185","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.119799999Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"Point\",\"slot\":351},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__REALTIME_TIMESTAMP":"1761317020250058","_TRANSPORT":"stdout","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75a;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=af5acec3428b2f37","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM":"1882","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"26973185"} +{"_GID":"10016","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.131554845Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317020250058","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"26973185","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75b;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=2f2bb47848d18629","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__SEQNUM":"1883","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759"} +{"_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75c;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=3baf516023f1cc7d","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.131690058Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":23,\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__SEQNUM":"1884","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_GID":"10016","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"26973185","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317020250058","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"26973185","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020250058","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75d;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=93f3cbb4a1c93cae","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.131732242Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_GID":"10016","__SEQNUM":"1885","_TRANSPORT":"stdout"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75e;b=082ebd52b7694299b9566558b64d809c;m=19b9401;t=641e893542fca;x=9da22b07e85ea042","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.131768559Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"26973185","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1886","PRIORITY":"6","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020250058","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"27021516","_TRANSPORT":"stdout","_COMM":"cardano-node","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.131826109Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"blockNo\":25,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":376},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020298389","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=75f;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=66b68b1f9d6988ed","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"1887","PRIORITY":"6"} +{"_UID":"10016","__REALTIME_TIMESTAMP":"1761317020298389","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=760;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=2284f946dc4422d0","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.132973461Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"5fc55ceaa91daf690f7cfdc0885bb87fc01e52196d53018e1da52525a26ee15a\",\"kind\":\"BlockPoint\",\"slot\":162}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM":"1888","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27021516","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0"} +{"__MONOTONIC_TIMESTAMP":"27021516","SYSLOG_FACILITY":"3","_PID":"759","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020298389","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.133028217Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":162}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=761;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=e750c89e8ea91f21","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM":"1889","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020298389","__MONOTONIC_TIMESTAMP":"27021516","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.133103086Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"delay\":1364055.119679313,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":863},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=762;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=9df566f050a96e4a","_GID":"10016","_CAP_EFFECTIVE":"0","_PID":"759","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__SEQNUM":"1890"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.133193042Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__SEQNUM":"1891","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=763;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=7fa688b89b6c5d02","__MONOTONIC_TIMESTAMP":"27021516","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317020298389"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=764;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=2fe2e21f8941fb22","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.133362896Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_GID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__SEQNUM":"1892","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27021516","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020298389"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"27021516","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__SEQNUM":"1893","_RUNTIME_SCOPE":"system","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=765;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=f9ab981f9c8ea5fc","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.140657678Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":376},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020298389","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_HOSTNAME":"leios-node"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27021516","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1894","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.141793576Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=766;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=61d8e0fdf89e25c1","__REALTIME_TIMESTAMP":"1761317020298389","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"__MONOTONIC_TIMESTAMP":"27021516","_PID":"759","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=767;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=dbfbce7bbfb0767d","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020298389","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__SEQNUM":"1895","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.148630479Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317020298389","_GID":"10016","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1896","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.148760942Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=768;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=a7f7e093036765c3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"27021516","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27021516","SYSLOG_FACILITY":"3","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_PID":"759","_UID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=769;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=55f58caf85df6585","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020298389","__SEQNUM":"1897","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.169946037Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_TRANSPORT":"stdout"} +{"__REALTIME_TIMESTAMP":"1761317020298389","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76a;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=9dadd36d3daaaaf","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.170014202Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27021516","_PID":"759","SYSLOG_FACILITY":"3","__SEQNUM":"1898","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.17588087Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"BlockPoint\",\"slot\":188},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317020298389","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27021516","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1899","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76b;b=082ebd52b7694299b9566558b64d809c;m=19c50cc;t=641e89354ec95;x=7ec9243bc79b09fb","_RUNTIME_SCOPE":"system","_GID":"10016","_TRANSPORT":"stdout"} +{"_GID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76c;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=bb0843c291bbf90a","__SEQNUM":"1900","__MONOTONIC_TIMESTAMP":"27099708","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.185452477Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":15,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":188,\"tieBreakVRF\":\"91e893c4158e01eb987b77c9a96c47e2f56716dcc543dbe2417472c5db49bf18969228fcc9453b03325ba7acc861c7321f21304cb125ee878a70244737335c61\"},\"newtip\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188\",\"oldTipSelectView\":{\"chainLength\":14,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":187,\"tieBreakVRF\":\"8919e2ddb190a3ed653847079a24279b39588139fa6d74620bdee5cf73b445aa454a8e1122e0d2133fb8f38e67aceaefa0d6981f90249ff40993e51e98fcecf8\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317020376578","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3"} +{"__REALTIME_TIMESTAMP":"1761317020376578","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__MONOTONIC_TIMESTAMP":"27099708","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76d;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=8b02b30322d36e80","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1901","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.18557903Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736@188\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76e;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=e0d91c2ced536f5","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.185661722Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020376578","__MONOTONIC_TIMESTAMP":"27099708","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM":"1902","_PID":"759"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1903","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020376578","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.185685747Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"Point\",\"slot\":222},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_UID":"10016","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=76f;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=992fdc3075908115","__MONOTONIC_TIMESTAMP":"27099708","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_GID":"10016","_HOSTNAME":"leios-node","_UID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__SEQNUM":"1904","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27099708","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020376578","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=770;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=f3c77fdbc91df3ec","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.249389095Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice"} +{"_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"27099708","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=771;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=652772ee6767415c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1905","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.249700308Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020376578","_COMM":"cardano-node","PRIORITY":"6"} +{"_SYSTEMD_SLICE":"system.slice","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=772;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=70d869308167975c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.274019041Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"a1ad392d2aa57f1003b968343db5293582b1fb334e24f0a592ca04a3594a5709\",\"kind\":\"BlockPoint\",\"slot\":179},\"head\":{\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"BlockPoint\",\"slot\":188}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1906","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"27099708","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020376578","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020376578","__SEQNUM":"1907","__MONOTONIC_TIMESTAMP":"27099708","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=773;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=e83f92454c5dc146","PRIORITY":"6","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.274077708Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"Point\",\"slot\":222},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27099708","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM":"1908","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_PID":"759","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.274160679Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=774;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=34ec5846a59f07","__REALTIME_TIMESTAMP":"1761317020376578"} +{"_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=775;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=2140b59add58006","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM":"1909","__MONOTONIC_TIMESTAMP":"27099708","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.274195041Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317020376578","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.292548211Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":179}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020376578","_CAP_EFFECTIVE":"0","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=776;b=082ebd52b7694299b9566558b64d809c;m=19d823c;t=641e893561e02;x=9d206a0fa7a47dbc","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1910","__MONOTONIC_TIMESTAMP":"27099708","_TRANSPORT":"stdout","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_GID":"10016"} +{"_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27177542","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1911","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.340749589Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"BlockPoint\",\"slot\":222},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=777;b=082ebd52b7694299b9566558b64d809c;m=19eb246;t=641e893574e0f;x=beed7b6d130950b0","_PID":"759","__REALTIME_TIMESTAMP":"1761317020454415","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service"} +{"_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27177542","__SEQNUM":"1912","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=778;b=082ebd52b7694299b9566558b64d809c;m=19eb246;t=641e893574e0f;x=873e908869a9f040","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.355534429Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":376},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317020454415","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=779;b=082ebd52b7694299b9566558b64d809c;m=19ee7f3;t=641e8935783b5;x=4aa5c6bfa8286d92","_CAP_EFFECTIVE":"0","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.368675485Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864@222\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020468149","__SEQNUM":"1913","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"27191283","_GID":"10016"} +{"__SEQNUM":"1914","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.368821034Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77a;b=082ebd52b7694299b9566558b64d809c;m=19f2234;t=641e89357bdf9;x=6fc1d39aedd92db8","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_GID":"10016","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317020483065","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"27206196","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77b;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=2a1f6736e0278ad7","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317020488964","__MONOTONIC_TIMESTAMP":"27212096","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.368860704Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"Point\",\"slot\":247},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM":"1915","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.394665939Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27212096","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77c;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=9c42ffd05e1f07b7","__REALTIME_TIMESTAMP":"1761317020488964","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1916"} +{"_PID":"759","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27212096","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020488964","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77d;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=4ba3b16fb152b3f9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.394808974Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":24,\"headerHash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1917","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_UID":"10016","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3"} +{"_PID":"759","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020488964","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"27212096","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77e;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=bd78ac0837e756d1","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.394859539Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1918","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_GID":"10016","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=77f;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=e3d020aa9ed78c61","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"27212096","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317020488964","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1919","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.405977712Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020488964","PRIORITY":"6","__SEQNUM":"1920","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=780;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=f13099b364c2372b","__MONOTONIC_TIMESTAMP":"27212096","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.406377762Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_PID":"759"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"27212096","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1921","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020488964","_PID":"759","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=781;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=38adb6ae12186c9b","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.42137492Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=782;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=4901e61cb12c2543","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.421421853Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__SEQNUM":"1922","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_RUNTIME_SCOPE":"system","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"27212096","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317020488964","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service"} +{"_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317020488964","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM":"1923","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.467202532Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"56515bfd5751ca2c1ca0f21050cdb1cd020e396c623a16a2274528f643d4b5fd\",\"kind\":\"BlockPoint\",\"slot\":183},\"head\":{\"headerHash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"BlockPoint\",\"slot\":222}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","__MONOTONIC_TIMESTAMP":"27212096","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=783;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=4fb08be66cb1c403","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020488964","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","PRIORITY":"6","__SEQNUM":"1924","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.467269021Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"Point\",\"slot\":247},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=784;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=9252b20225a5795a","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27212096","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_PID":"759"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"27212096","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_PID":"759","__REALTIME_TIMESTAMP":"1761317020488964","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_UID":"10016","__SEQNUM":"1925","PRIORITY":"6","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=785;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=52c06a519b8381cb","_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.467360094Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016"} +{"SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1926","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=786;b=082ebd52b7694299b9566558b64d809c;m=19f3940;t=641e89357d504;x=884ef474bf0eefb6","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.467395853Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"27212096","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020488964","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27290411","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=787;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=63f177578a1b9949","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020567284","_PID":"759","PRIORITY":"6","__SEQNUM":"1927","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.474523854Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_GID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"27290411","__REALTIME_TIMESTAMP":"1761317020567284","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.474615485Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"blockNo\":26,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":392},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1928","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=788;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=e80eab5590b0af75","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_TRANSPORT":"stdout","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=789;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=48d932d32c53ebf4","_PID":"759","_UID":"10016","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.476697035Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":219478168,\"CentiBlkIO\":0,\"CentiCpu\":91,\"CentiGC\":2,\"CentiMut\":82,\"FsRd\":50864128,\"FsWr\":118784,\"GcsMajor\":2,\"GcsMinor\":5,\"Heap\":49283072,\"Live\":4105288,\"NetRd\":0,\"NetWr\":0,\"RSS\":99745792,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27290411","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317020567284","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1929","_RUNTIME_SCOPE":"system"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM":"1930","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"27290411","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78a;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=2f60beb1446933d9","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317020567284","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.477394051Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78b;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=1d10432b3a07cdf6","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27290411","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.477519765Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":25,\"headerHash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020567284","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__SEQNUM":"1931","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78c;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=b1ade80260486df4","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.477563067Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"27290411","__SEQNUM":"1932","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020567284","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_GID":"10016","__REALTIME_TIMESTAMP":"1761317020567284","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27290411","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM":"1933","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78d;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=635b33da6dc85674","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.477601619Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"SYSLOG_FACILITY":"3","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78e;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=97616fe60c4ecf50","_RUNTIME_SCOPE":"system","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27290411","__REALTIME_TIMESTAMP":"1761317020567284","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.477659727Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"blockNo\":27,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":397},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"1934"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"27290411","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=78f;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=c2f80ded49925077","SYSLOG_FACILITY":"3","_GID":"10016","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.479522254Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"BlockPoint\",\"slot\":247},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020567284","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM":"1935","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1936","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27290411","PRIORITY":"6","_PID":"759","__REALTIME_TIMESTAMP":"1761317020567284","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.479949404Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=790;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=821ba8b969e47102"} +{"_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1937","_GID":"10016","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.480027346Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":26,\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020567284","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27290411","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=791;b=082ebd52b7694299b9566558b64d809c;m=1a06b2b;t=641e8935906f4;x=b5a65814b254816f","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout"} +{"_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=792;b=082ebd52b7694299b9566558b64d809c;m=1a1a56a;t=641e8935a3ff4;x=22b424871b8bf72f","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"27370858","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.480056959Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317020647412","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"1938"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__MONOTONIC_TIMESTAMP":"27376958","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317020653831","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=793;b=082ebd52b7694299b9566558b64d809c;m=1a1bd3e;t=641e8935a5907;x=2bff35490bf5bffd","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:39.79381192 UTC to 2025-10-24 14:43:40.65338206 UTC","__SEQNUM":"1939","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_GID":"10016","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=794;b=082ebd52b7694299b9566558b64d809c;m=1a200c4;t=641e8935a9c86;x=eafe3679a10a7c9d","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020671110","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27394244","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.48008294Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_PID":"759","_UID":"10016","__SEQNUM":"1940","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout"} +{"_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_HOSTNAME":"leios-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"27405174","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.480123169Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"blockNo\":28,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":444},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=795;b=082ebd52b7694299b9566558b64d809c;m=1a22b76;t=641e8935ac674;x=366f96079fd4ccb0","__SEQNUM":"1941","__REALTIME_TIMESTAMP":"1761317020681844","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=796;b=082ebd52b7694299b9566558b64d809c;m=1a24aea;t=641e8935ae6b2;x=e02920880d4b6c14","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1942","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.4809892Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9@247\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317020690098","__MONOTONIC_TIMESTAMP":"27413226","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"27421325","__REALTIME_TIMESTAMP":"1761317020698195","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=797;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=1141ad89b171a311","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__SEQNUM":"1943","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.481065747Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317020698195","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.48109061Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"Point\",\"slot\":280},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__SEQNUM":"1944","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=798;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=d928216426c9e601","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"27421325","_PID":"759","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3"} +{"_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020698195","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27421325","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.481399308Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"60fd8fc00994ac1d3901f1d7a777edf5b99546a748fc7de8694cc165339d5d11\",\"kind\":\"BlockPoint\",\"slot\":187},\"head\":{\"headerHash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"BlockPoint\",\"slot\":247}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1945","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=799;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=4f359f64da1e4597","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.481432832Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"Point\",\"slot\":280},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79a;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=1daa431e6c91adab","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_PID":"759","__REALTIME_TIMESTAMP":"1761317020698195","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27421325","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM":"1946","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_GID":"10016","__REALTIME_TIMESTAMP":"1761317020698195","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79b;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=778bc1f496db4154","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__SEQNUM":"1947","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"27421325","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.481483397Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79c;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=d7e63c440b2a179","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1948","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.481503512Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"27421325","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_UID":"10016","_PID":"759","__REALTIME_TIMESTAMP":"1761317020698195"} +{"_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1949","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79d;b=082ebd52b7694299b9566558b64d809c;m=1a26a8d;t=641e8935b0653;x=cc00b3c30d6d9d65","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020698195","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.482057213Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":444},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27421325"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM":"1950","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79e;b=082ebd52b7694299b9566558b64d809c;m=1a31e22;t=641e8935bb9eb;x=41209b075ecc6b76","__REALTIME_TIMESTAMP":"1761317020744171","_TRANSPORT":"stdout","_UID":"10016","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27467298","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.487710725Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.4878451Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","_GID":"10016","_COMM":"cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"27472643","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=79f;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=296a3770ca3b145","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1951","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_PID":"759","_RUNTIME_SCOPE":"system","PRIORITY":"6","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317020749515"} +{"__MONOTONIC_TIMESTAMP":"27472643","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.531838121Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":183}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a0;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=bd4b4c5b79a71e58","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1952","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317020749515","_PID":"759"} +{"_PID":"759","__REALTIME_TIMESTAMP":"1761317020749515","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a1;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=99f198107af01fe5","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.566718532Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27472643","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__SEQNUM":"1953"} +{"__SEQNUM":"1954","_UID":"10016","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"27472643","__REALTIME_TIMESTAMP":"1761317020749515","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a2;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=43bd770fd040288f","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.573539231Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM":"1955","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020749515","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a3;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=115ccad546b0a892","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__MONOTONIC_TIMESTAMP":"27472643","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.575628324Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"BlockPoint\",\"slot\":280},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_PID":"759","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice"} +{"__MONOTONIC_TIMESTAMP":"27472643","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.575846787Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db@280\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020749515","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__SEQNUM":"1956","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a4;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=383d0e6bda80b9de","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_TRANSPORT":"stdout"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.615710513Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__MONOTONIC_TIMESTAMP":"27472643","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a5;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=c92dcc8e24d5e60","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1957","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317020749515","_TRANSPORT":"stdout","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_PID":"759","__REALTIME_TIMESTAMP":"1761317020749515","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.615756049Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"Point\",\"slot\":304},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27472643","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"1958","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a6;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=2d3bd10af794004c"} +{"_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a7;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=b1dc4e8cc5e66452","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"1959","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317020749515","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_GID":"10016","__MONOTONIC_TIMESTAMP":"27472643","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.615860252Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"Point\",\"slot\":304},\"blockNo\":\"19\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016"} +{"_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a8;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=971787a02398287f","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__MONOTONIC_TIMESTAMP":"27472643","__REALTIME_TIMESTAMP":"1761317020749515","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__SEQNUM":"1960","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.632274909Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27472643","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.632522147Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"Point\",\"slot\":376},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_UID":"10016","_TRANSPORT":"stdout","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","PRIORITY":"6","__SEQNUM":"1961","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7a9;b=082ebd52b7694299b9566558b64d809c;m=1a33303;t=641e8935bcecb;x=932f404abd68d349","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020749515","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317020819331","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_GID":"10016","_UID":"10016","__SEQNUM":"1962","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7aa;b=082ebd52b7694299b9566558b64d809c;m=1a443bb;t=641e8935cdf83;x=231732448a927fe4","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.63266574Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27542459"} +{"__MONOTONIC_TIMESTAMP":"27542459","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.647677984Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":444},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317020819331","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_GID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ab;b=082ebd52b7694299b9566558b64d809c;m=1a443bb;t=641e8935cdf83;x=e6332492ea8e70b2","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1963","SYSLOG_FACILITY":"3","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"27558086","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ac;b=082ebd52b7694299b9566558b64d809c;m=1a480c6;t=641e8935d1c8c;x=fa1720dd88bcdb1c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020834956","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_UID":"10016","__SEQNUM":"1964","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.65338206Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"BlockPoint\",\"slot\":188},\"head\":{\"headerHash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"BlockPoint\",\"slot\":280}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","PRIORITY":"6","_TRANSPORT":"stdout","_COMM":"cardano-node","_UID":"10016","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.653419216Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"Point\",\"slot\":304},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020845090","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ad;b=082ebd52b7694299b9566558b64d809c;m=1a4a860;t=641e8935d4422;x=24600736633636e5","__MONOTONIC_TIMESTAMP":"27568224","__SEQNUM":"1965","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"27573278","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.658407839Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020850151","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ae;b=082ebd52b7694299b9566558b64d809c;m=1a4bc1e;t=641e8935d57e7;x=c8e86a13b6f73f1b","__SEQNUM":"1966","_PID":"759","PRIORITY":"6"} +{"_PID":"759","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317020850151","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"27573278","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.658636639Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7af;b=082ebd52b7694299b9566558b64d809c;m=1a4bc1e;t=641e8935d57e7;x=cd6f4cf3728762c6","_GID":"10016","__SEQNUM":"1967","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"27586099","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1968","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317020862972","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b0;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=b4967a21239bf5b6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_PID":"759","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.660782722Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":187}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016"} +{"_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.664256348Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","_UID":"10016","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"27586099","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b1;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=7424225ef009a6c4","__REALTIME_TIMESTAMP":"1761317020862972","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_COMM":"cardano-node","__SEQNUM":"1969","SYSLOG_FACILITY":"3","PRIORITY":"6","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:40.669143561Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"48cf5b44cb529d51b5b90c8b7c2572a27a2f22fc8933fe51eeb23891fb1a9736\",\"kind\":\"BlockPoint\",\"slot\":188}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b2;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=da4888f37f465c6a","_CAP_EFFECTIVE":"0","_PID":"759","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"27586099","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317020862972","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1970","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_UID":"10016"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020862972","SYSLOG_FACILITY":"3","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27586099","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"1971","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.669217593Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":188}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b3;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=2f1add00e000695a","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.670518317Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"BlockPoint\",\"slot\":304},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1972","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b4;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=897ea7e3ecc418cf","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317020862972","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_GID":"10016","__MONOTONIC_TIMESTAMP":"27586099","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"__SEQNUM":"1973","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317020862972","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b5;b=082ebd52b7694299b9566558b64d809c;m=1a4ee33;t=641e8935d89fc;x=c6918ad53d11d12e","_UID":"10016","PRIORITY":"6","_PID":"759","__MONOTONIC_TIMESTAMP":"27586099","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.677704705Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7@304\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b6;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=40a88cbb226743a9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.677815613Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"1974","PRIORITY":"6","_CAP_EFFECTIVE":"0","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020900509","_COMM":"cardano-node","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"27623639","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1975","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27623639","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317020900509","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b7;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=456052629693a88b","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.677841314Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"Point\",\"slot\":325},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27623639","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020900509","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"1976","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b8;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=5697ba944fc1f4cf","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.679856934Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7b9;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=bd2f8a2d3777d05a","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317020900509","_GID":"10016","__SEQNUM":"1977","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27623639","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680027067Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":27,\"headerHash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__REALTIME_TIMESTAMP":"1761317020900509","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ba;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=8ff634f659570621","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680061708Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1978","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27623639","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__SEQNUM":"1979","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020900509","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7bb;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=4a5f091b0d42c77e","_PID":"759","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"27623639","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680088527Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"1980","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7bc;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=eeeeeec649f34a93","__MONOTONIC_TIMESTAMP":"27623639","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317020900509","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680130711Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"blockNo\":29,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":487},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","PRIORITY":"6"} +{"_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317020900509","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680380464Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":487},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","__SEQNUM":"1981","_CAP_EFFECTIVE":"0","PRIORITY":"6","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"27623639","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7bd;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=862b224f85074d14","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__REALTIME_TIMESTAMP":"1761317020900509","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","SYSLOG_FACILITY":"3","_PID":"759","__SEQNUM":"1982","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7be;b=082ebd52b7694299b9566558b64d809c;m=1a580d7;t=641e8935e1c9d;x=9df38837a97ce7c6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.680828845Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27623639"} +{"__SEQNUM":"1983","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.683345086Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0a723e7ee49160fcf5a652bcff9f0435187e5fc239a6a8f816d3960fc6cf6864\",\"kind\":\"BlockPoint\",\"slot\":222},\"head\":{\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"BlockPoint\",\"slot\":304}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_TRANSPORT":"stdout","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_UID":"10016","__MONOTONIC_TIMESTAMP":"27679357","PRIORITY":"6","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020956227","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7bf;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=1c4c379b398f42e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1984","__MONOTONIC_TIMESTAMP":"27679357","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c0;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=5d7a1abf00e08f8e","_GID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.683384756Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"Point\",\"slot\":325},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020956227","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c1;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=faedcc2d782c7e97","_UID":"10016","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317020956227","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.710800252Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27679357","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","PRIORITY":"6","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__SEQNUM":"1985","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_UID":"10016","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.72030118Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27679357","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020956227","_GID":"10016","_PID":"759","__SEQNUM":"1986","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c2;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=7465912e7957d0b","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c3;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=52853980f8a4bd0e","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__REALTIME_TIMESTAMP":"1761317020956227","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.720677764Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"delay\":1364014.720444494,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"1987","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_RUNTIME_SCOPE":"system","_UID":"10016","__MONOTONIC_TIMESTAMP":"27679357","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node"} +{"PRIORITY":"6","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317020956227","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"1988","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c4;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=439e064575790041","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.683455715Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__MONOTONIC_TIMESTAMP":"27679357","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756445997Z\",\"ns\":\"StateQueryServer.Receive.Release\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgRelease\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","_GID":"10016","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317020956227","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c5;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=37132082808cefa9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27679357","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1989"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1990","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","PRIORITY":"6","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"27679357","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317020956227","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756515559Z\",\"ns\":\"StateQueryServer.Receive.Done\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgDone\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"}},\"sev\":\"Info\",\"thread\":\"88\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c6;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=1aeed3c3f1f80233"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c7;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=91c333624866a11f","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"1991","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.710931274Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27679357","_PID":"759","__REALTIME_TIMESTAMP":"1761317020956227","_TRANSPORT":"stdout","_HOSTNAME":"leios-node"} +{"_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"1992","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_TRANSPORT":"stdout","_UID":"10016","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.743672307Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c8;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=e362ec7950acfa8c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27679357","__REALTIME_TIMESTAMP":"1761317020956227","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_CAP_EFFECTIVE":"0","__SEQNUM":"1993","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7c9;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=4be6d57876cb85e9","__MONOTONIC_TIMESTAMP":"27679357","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317020956227","_PID":"759","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756691559Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3"} +{"__REALTIME_TIMESTAMP":"1761317020956227","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ca;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=a8bf8c4f007c2518","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"1994","_GID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27679357","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756720334Z\",\"ns\":\"Net.InboundGovernor.Local.WaitIdleRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"WaitIdleRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundSt\"}}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice"} +{"_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7cb;b=082ebd52b7694299b9566558b64d809c;m=1a65a7d;t=641e8935ef643;x=f086e12d719d3b56","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317020956227","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756753299Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27679357","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","SYSLOG_FACILITY":"3","PRIORITY":"6","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"1995"} +{"__REALTIME_TIMESTAMP":"1761317021050185","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756786264Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__SEQNUM":"1996","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7cc;b=082ebd52b7694299b9566558b64d809c;m=1a7c981;t=641e893606549;x=bff4212dae13ec1","_PID":"759","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"27773313","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_SLICE":"system.slice","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"27782188","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7cd;b=082ebd52b7694299b9566558b64d809c;m=1a7ec2c;t=641e8936087de;x=dc9dcb56eb8597fe","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"1997","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317021059038","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.756853591Z\",\"ns\":\"Net.InboundGovernor.Local.ResponderRestarted\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"ResponderStarted\",\"miniProtocolNum\":{\"kind\":\"MiniProtocolNum\",\"num\":7}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_GID":"10016"} +{"_GID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.779177937Z\",\"ns\":\"Net.Mux.Local.CleanExit\",\"data\":{\"bearer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@1\\\"\"},\"event\":{\"kind\":\"Mux.TraceCleanExit\",\"miniProtocolDir\":\"ResponderDir\",\"miniProtocolNum\":\"MiniProtocolNum 7\",\"msg\":\"Miniprotocol terminated cleanly\"},\"kind\":\"Mux.Trace\"},\"sev\":\"Notice\",\"thread\":\"85\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","PRIORITY":"6","_HOSTNAME":"leios-node","_PID":"759","__SEQNUM":"1998","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021068592","__MONOTONIC_TIMESTAMP":"27791719","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ce;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=d3fc8957a059d5c9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM":"1999","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7cf;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=8d0b64d564ce85a6","__MONOTONIC_TIMESTAMP":"27791719","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021068592","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.811323084Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_PID":"759"} +{"_UID":"10016","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM":"2000","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d0;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=1fe1511751643f75","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27791719","__REALTIME_TIMESTAMP":"1761317021068592","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.818585459Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_PID":"759","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service"} +{"__SEQNUM":"2001","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_UID":"10016","__MONOTONIC_TIMESTAMP":"27791719","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d1;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=61e3d4d337202bb6","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.828725575Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"BlockPoint\",\"slot\":325},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021068592"} +{"__REALTIME_TIMESTAMP":"1761317021068592","__SEQNUM":"2002","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.82957233Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28@325\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d2;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=70c55ab87cfe0cd6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_GID":"10016","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"27791719","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CAP_EFFECTIVE":"0","_UID":"10016","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27791719","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.831133702Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d3;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=fa0f22c3e50dd194","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__REALTIME_TIMESTAMP":"1761317021068592","__SEQNUM":"2003","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d4;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=838dc3d53fd9c819","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2004","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317021068592","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27791719","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.831323391Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"Point\",\"slot\":333},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_COMM":"cardano-node"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2005","_GID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.83303562Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":222}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27791719","_UID":"10016","_PID":"759","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d5;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=5ff2c2f7c64d4cff","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317021068592","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_PID":"759","__SEQNUM":"2006","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.833359683Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"85d81d95904511cde7f086e20b8ee83680dd741546d8a0d6a715373055efdac9\",\"kind\":\"BlockPoint\",\"slot\":247},\"head\":{\"headerHash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"BlockPoint\",\"slot\":325}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"27791719","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d6;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=3ab61f6881800812","_TRANSPORT":"stdout","_UID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021068592","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27791719","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.833394604Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"Point\",\"slot\":333},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d7;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=2a2cb5dbc86092b9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_PID":"759","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021068592","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2007"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d8;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=e8349122dbaa02ba","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021068592","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.833445169Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2008","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27791719","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_TRANSPORT":"stdout"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.83408268Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":487},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__SEQNUM":"2009","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7d9;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=f7aa63a6d79825b0","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021068592","_UID":"10016","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27791719","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"27791719","__SEQNUM":"2010","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.833482604Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","__REALTIME_TIMESTAMP":"1761317021068592","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7da;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=d8dbfaeaaa356aa7","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__REALTIME_TIMESTAMP":"1761317021068592","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27791719","_TRANSPORT":"stdout","PRIORITY":"6","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7db;b=082ebd52b7694299b9566558b64d809c;m=1a81167;t=641e89360ad30;x=733ed43307b76ad7","__SEQNUM":"2011","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.842681818Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"27891110","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_GID":"10016","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.905429178Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"BlockPoint\",\"slot\":333},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7dc;b=082ebd52b7694299b9566558b64d809c;m=1a995a6;t=641e893623169;x=f6778015e0b58ac1","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021167977","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM":"2012","_COMM":"cardano-node"} +{"_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2013","__MONOTONIC_TIMESTAMP":"27897644","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021174514","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.905663007Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0@333\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7dd;b=082ebd52b7694299b9566558b64d809c;m=1a9af2c;t=641e893624af2;x=dc3c5ae9c57aecf0","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.905773356Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021179943","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"27903072","__SEQNUM":"2014","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7de;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=4cc802b168bce71c","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2015","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7df;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=745bc504e3bf53ab","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.905811629Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"Point\",\"slot\":351},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"27903072","PRIORITY":"6","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317021179943","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"__SEQNUM":"2016","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e0;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=b999c5fa92c8edcf","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_COMM":"cardano-node","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.943463621Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"af465feeaa8b06a46ac853bc81f05d2f26ac3ffb887d9430438d21dee46237db\",\"kind\":\"BlockPoint\",\"slot\":280},\"head\":{\"headerHash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"BlockPoint\",\"slot\":333}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317021179943","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"27903072"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317021179943","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.94350357Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"Point\",\"slot\":351},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e1;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=bba267a2bf50faa7","_GID":"10016","__SEQNUM":"2017","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"27903072","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e2;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=61f80009c5127ba9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__MONOTONIC_TIMESTAMP":"27903072","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317021179943","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2018","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.943558605Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.943579558Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e3;b=082ebd52b7694299b9566558b64d809c;m=1a9c460;t=641e893626027;x=399b634c5b01aefa","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317021179943","__MONOTONIC_TIMESTAMP":"27903072","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__SEQNUM":"2019","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","PRIORITY":"6","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_PID":"759","__MONOTONIC_TIMESTAMP":"27939568","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e4;b=082ebd52b7694299b9566558b64d809c;m=1aa52f0;t=641e89362eeb8;x=8bc97298493eb322","_GID":"10016","__SEQNUM":"2020","_RUNTIME_SCOPE":"system","_UID":"10016","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:40.981710381Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"BlockPoint\",\"slot\":351},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021216440","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__SEQNUM":"2021","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.004162956Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","PRIORITY":"6","_GID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e5;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=6a2872bddf6e719a","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27948071","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317021224942","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_PID":"759","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"27948071","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021224942","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.004610778Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_PID":"759","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM":"2022","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e6;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=e441e9ab6554e573","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3"} +{"__MONOTONIC_TIMESTAMP":"27948071","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e7;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=1c0cdc3614f3ac47","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2023","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021224942","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.005615096Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":28,\"headerHash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.005670131Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021224942","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e8;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=f02433ff1bc0d4ff","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2024","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"27948071"} +{"_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7e9;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=13581da7635d1440","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","PRIORITY":"6","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.005712873Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317021224942","_GID":"10016","__SEQNUM":"2025","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__MONOTONIC_TIMESTAMP":"27948071"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317021224942","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM":"2026","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27948071","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ea;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=4a43b3459a148f0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.005796962Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"blockNo\":30,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":505},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_PID":"759","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7eb;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=fdaef86e71297069","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021224942","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.033466959Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9@351\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2027","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27948071","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317021224942","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ec;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=c889d601d62b0662","__MONOTONIC_TIMESTAMP":"27948071","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.033587925Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM":"2028","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__REALTIME_TIMESTAMP":"1761317021224942","__MONOTONIC_TIMESTAMP":"27948071","_SYSTEMD_SLICE":"system.slice","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","__SEQNUM":"2029","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ed;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=d8f538d4922279c9","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.03362955Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"Point\",\"slot\":357},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021224942","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.043259545Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":247}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM":"2030","_UID":"10016","__MONOTONIC_TIMESTAMP":"27948071","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ee;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=93112fd6e344276d","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_GID":"10016","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.056559559Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"BlockPoint\",\"slot\":304},\"head\":{\"headerHash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"BlockPoint\",\"slot\":351}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ef;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=30a663890d3c61c4","__REALTIME_TIMESTAMP":"1761317021224942","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"27948071","_HOSTNAME":"leios-node","__SEQNUM":"2031","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice"} +{"SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f0;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=738989d5cdfa1b2b","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317021224942","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"27948071","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.056599508Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"Point\",\"slot\":357},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2032","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.056655661Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f1;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=cf98ef0bf2681bb4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"27948071","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2033","_PID":"759","__REALTIME_TIMESTAMP":"1761317021224942","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_CAP_EFFECTIVE":"0","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f2;b=082ebd52b7694299b9566558b64d809c;m=1aa7427;t=641e893630fee;x=68333dd8a9b295ef","__REALTIME_TIMESTAMP":"1761317021224942","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.056675775Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"27948071","_UID":"10016","__SEQNUM":"2034","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759"} +{"_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28029572","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f3;b=082ebd52b7694299b9566558b64d809c;m=1abb284;t=641e893644e4c;x=63f6e2924df0b6cc","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317021306444","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.117104405Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"BlockPoint\",\"slot\":357},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2035"} +{"_CAP_EFFECTIVE":"0","__SEQNUM":"2036","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021306444","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f4;b=082ebd52b7694299b9566558b64d809c;m=1abb284;t=641e893644e4c;x=bd3845f4cd330ed2","_PID":"759","__MONOTONIC_TIMESTAMP":"28029572","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.122734171Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.137193271Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":23,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":357,\"tieBreakVRF\":\"868112c5d3009e4ce6af8eb8d84451a582e29b0eea12c17dc184b53cfd6b6b01de90f9b31d54bb76558fe365239832267bf04588604d2edbfe9e847b9df6f47e\"},\"newtip\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357\",\"oldTipSelectView\":{\"chainLength\":22,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":351,\"tieBreakVRF\":\"b6a8cc7687446779bdf7584a9715902baeb2098cc1b419479a3ff3fdc81d8aec7b3b9acc2b50a51fa8f6eab3dd59c427db5534a8867a1300b15551acc6a19a9f\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021321952","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"28045083","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f5;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=641486adaf50448b","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM":"2037","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_UID":"10016","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f6;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=f38fd2121cc5af61","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021321952","_TRANSPORT":"stdout","_GID":"10016","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.137355023Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704@357\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"28045083","__SEQNUM":"2038","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28045083","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.137443303Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM":"2039","__REALTIME_TIMESTAMP":"1761317021321952","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f7;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=5f923b2747c42261","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system"} +{"_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.137469563Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"Point\",\"slot\":362},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f8;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=a67da6cfffb398d7","PRIORITY":"6","_COMM":"cardano-node","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28045083","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021321952","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_GID":"10016","__SEQNUM":"2040","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice"} +{"_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","_PID":"759","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__SEQNUM":"2041","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.137565665Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"Point\",\"slot\":362},\"blockNo\":\"24\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317021321952","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7f9;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=bfcc350172de2c20","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28045083","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.163437668Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_GID":"10016","_PID":"759","__SEQNUM":"2042","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7fa;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=cd16a3a6d6787004","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317021321952","__MONOTONIC_TIMESTAMP":"28045083","_UID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_TRANSPORT":"stdout"} +{"PRIORITY":"6","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021321952","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2043","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7fb;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=7930ff5b3d2006a","__MONOTONIC_TIMESTAMP":"28045083","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.16349382Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"_PID":"759","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28045083","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM":"2044","__REALTIME_TIMESTAMP":"1761317021321952","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7fc;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=175bf31d9e44e444","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.167364145Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"a55ea784553ee268b0454be7bf05922d36860ef068deea9478c4d679e710cc28\",\"kind\":\"BlockPoint\",\"slot\":325},\"head\":{\"headerHash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"BlockPoint\",\"slot\":357}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016"} +{"_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021321952","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.167421694Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"Point\",\"slot\":362},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7fd;b=082ebd52b7694299b9566558b64d809c;m=1abef1b;t=641e893648ae0;x=b2d1dca9d89f0ee1","__SEQNUM":"2045","__MONOTONIC_TIMESTAMP":"28045083","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759"} +{"_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","PRIORITY":"6","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2046","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"28110079","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317021386948","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7fe;b=082ebd52b7694299b9566558b64d809c;m=1acecff;t=641e8936588c4;x=a846221bb2196997","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.16750271Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:41.167534837Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__MONOTONIC_TIMESTAMP":"28117114","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=7ff;b=082ebd52b7694299b9566558b64d809c;m=1ad087a;t=641e89365a441;x=708addc34ce5023f","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__SEQNUM":"2047","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021393985","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__REALTIME_TIMESTAMP":"1761317021399948","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2048","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__MONOTONIC_TIMESTAMP":"28123076","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.223533574Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"BlockPoint\",\"slot\":362},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=800;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=74345e38852bccfe","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.241827799Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e@362\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=801;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=ddecac49da3e13ef","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2049","__MONOTONIC_TIMESTAMP":"28123076","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021399948","PRIORITY":"6"} +{"_GID":"10016","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28123076","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317021399948","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2050","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.251188765Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=802;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=120e5cadc66d051a","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node"} +{"_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=803;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=ae0196a4342d48a3","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021399948","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28123076","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.251220054Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"Point\",\"slot\":376},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","PRIORITY":"6","_PID":"759","__SEQNUM":"2051","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28123076","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","__REALTIME_TIMESTAMP":"1761317021399948","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__SEQNUM":"2052","PRIORITY":"6","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.25154272Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"81087aadaf0aa08e185e7d72e932fd380a16870c72a1136f8c6fcef21a555fa0\",\"kind\":\"BlockPoint\",\"slot\":333},\"head\":{\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"BlockPoint\",\"slot\":362}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=804;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=9f3d33e87c2ac091","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28123076","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.251576244Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"Point\",\"slot\":376},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_PID":"759","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021399948","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2053","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=805;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=4ef644207cb05cfa"} +{"PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_PID":"759","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.251628765Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=806;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=124ba2748b39c14f","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2054","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28123076","__REALTIME_TIMESTAMP":"1761317021399948","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28123076","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=807;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=e14dbce8dbe5db23","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2055","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021399948","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.25164832Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice"} +{"__MONOTONIC_TIMESTAMP":"28123076","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.264427878Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"05f2b94c2a0427a32c01065299ffbc8f231f73185f3bdbc6a465238a09e3b1e7\",\"kind\":\"BlockPoint\",\"slot\":304}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317021399948","_CAP_EFFECTIVE":"0","_PID":"759","_UID":"10016","__SEQNUM":"2056","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=808;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=5617668d2ab53624","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_GID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"28123076","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2057","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=809;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=e680b45e202e1247","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.26449744Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":304}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","PRIORITY":"6","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021399948","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80a;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=d7ca5c3cc04fe19e","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2058","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021399948","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_GID":"10016","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28123076","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.280301962Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80b;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=c455e4464946662c","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28123076","_RUNTIME_SCOPE":"system","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM":"2059","PRIORITY":"6","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021399948","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.280417619Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":29,\"headerHash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021399948","__SEQNUM":"2060","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80c;b=082ebd52b7694299b9566558b64d809c;m=1ad1fc4;t=641e89365bb8c;x=477d13c6bdc1acab","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.280452261Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28123076","_RUNTIME_SCOPE":"system","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"__SEQNUM":"2061","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317021480138","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80d;b=082ebd52b7694299b9566558b64d809c;m=1ae5902;t=641e89366f4ca;x=22fb31b3543809a0","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28203266","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:40.653419216 UTC to 2025-10-24 14:43:41.393051208 UTC"} +{"__REALTIME_TIMESTAMP":"1761317021485278","_COMM":"cardano-node","_UID":"10016","__SEQNUM":"2062","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80e;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=203d5ee82cec05d","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.2804788Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28208407","_GID":"10016","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"28208407","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=80f;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=90fa1dc4f2fbc660","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2063","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317021485278","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.280520426Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"blockNo\":31,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":558},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=810;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=525eb07497db4217","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.280779677Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":558},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_GID":"10016","_TRANSPORT":"stdout","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"28208407","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2064","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021485278"} +{"__REALTIME_TIMESTAMP":"1761317021485278","__SEQNUM":"2065","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28208407","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.299508873Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_GID":"10016","_CAP_EFFECTIVE":"0","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=811;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=66bfaea01cfb2b1f","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_COMM":"cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317021485278","__MONOTONIC_TIMESTAMP":"28208407","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=812;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=e0bb707c4d9a4611","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__SEQNUM":"2066","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.317559491Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice"} +{"_GID":"10016","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28208407","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=813;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=aae1cfe83689734","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2067","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.3176081Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021485278","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.318424126Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"BlockPoint\",\"slot\":376},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"28208407","_HOSTNAME":"leios-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317021485278","_PID":"759","_RUNTIME_SCOPE":"system","__SEQNUM":"2068","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=814;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=40697d82f2bbe62c"} +{"_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=815;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=e557e44ce35626fd","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021485278","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.318578894Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c@376\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28208407","__SEQNUM":"2069"} +{"_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=816;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=60e8f26dc67a3bfe","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"28208407","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.318649294Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317021485278","__SEQNUM":"2070","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__SEQNUM":"2071","_PID":"759","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.318673599Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"Point\",\"slot\":392},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317021485278","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28208407","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=817;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=a9198459e863c89b","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_RUNTIME_SCOPE":"system","_UID":"10016","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021485278","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"28208407","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2072","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=818;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=9215c6c6ff3b40aa","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.319599135Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":333}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_PID":"759","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016"} +{"_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.320225472Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"e8cc9be2eba6b2b5cc1ee4e234696ed42eb8bfc547361215fa0d5b20fcee63d9\",\"kind\":\"BlockPoint\",\"slot\":351},\"head\":{\"headerHash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"BlockPoint\",\"slot\":376}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","PRIORITY":"6","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28208407","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_UID":"10016","__REALTIME_TIMESTAMP":"1761317021485278","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2073","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=819;b=082ebd52b7694299b9566558b64d809c;m=1ae6d17;t=641e8936708de;x=db0ee55be81389af","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.320280786Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"Point\",\"slot\":392},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28276509","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317021553379","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81a;b=082ebd52b7694299b9566558b64d809c;m=1af771d;t=641e8936812e3;x=584905d839ec041d","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__SEQNUM":"2074"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81b;b=082ebd52b7694299b9566558b64d809c;m=1af771d;t=641e8936812e3;x=6c72f642c57fabb2","_UID":"10016","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28276509","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.320364037Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021553379","_GID":"10016","__SEQNUM":"2075","_PID":"759","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3"} +{"_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021553379","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81c;b=082ebd52b7694299b9566558b64d809c;m=1af771d;t=641e8936812e3;x=262a21a44b0f1fcd","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM":"2076","SYSLOG_FACILITY":"3","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.32039812Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28276509","_GID":"10016","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_UID":"10016","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28276509","__SEQNUM":"2077","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317021553379","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81d;b=082ebd52b7694299b9566558b64d809c;m=1af771d;t=641e8936812e3;x=217cb413ae565d5e","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.321176431Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":351}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout"} +{"_TRANSPORT":"stdout","_GID":"10016","__REALTIME_TIMESTAMP":"1761317021577277","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.377297809Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"BlockPoint\",\"slot\":392},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28300407","__SEQNUM":"2078","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81e;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=1cec3f91227cbedd","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0"} +{"_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021577277","PRIORITY":"6","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2079","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.377474648Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3@392\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28300407","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=81f;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=8e1e36e745a55b2d","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__SEQNUM":"2080","__REALTIME_TIMESTAMP":"1761317021577277","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=820;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=e61608297c91019a","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.377555384Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28300407","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_PID":"759","__SEQNUM":"2081","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=821;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=a75aef2a366821f","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021577277","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.377598965Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"Point\",\"slot\":397},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"28300407","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=822;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=5862e2d1b176008","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2082","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021577277","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.383590509Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__MONOTONIC_TIMESTAMP":"28300407","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=823;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=d6e7f7876fa31019","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__SEQNUM":"2083","__REALTIME_TIMESTAMP":"1761317021577277","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.384580579Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"82758a7911fef3cf13add63c23f6113720117acf2944c43c443518332db44704\",\"kind\":\"BlockPoint\",\"slot\":357},\"head\":{\"headerHash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"BlockPoint\",\"slot\":392}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28300407","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_UID":"10016","__MONOTONIC_TIMESTAMP":"28300407","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"2084","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317021577277","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=824;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=ae06193aeabee819","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.384652096Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"Point\",\"slot\":397},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__REALTIME_TIMESTAMP":"1761317021577277","_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=825;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=7b446d7575c47bfa","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","PRIORITY":"6","_GID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2085","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.38474708Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_UID":"10016","__MONOTONIC_TIMESTAMP":"28300407","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=826;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=6e7dc95fb970a470","_TRANSPORT":"stdout","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","__MONOTONIC_TIMESTAMP":"28300407","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__REALTIME_TIMESTAMP":"1761317021577277","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_GID":"10016","__SEQNUM":"2086","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.38479122Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2087","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=827;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=7d9240d236cd5a02","__REALTIME_TIMESTAMP":"1761317021577277","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.385705023Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":558},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28300407","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__SEQNUM":"2088","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=828;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=1b36a2a9992b9e39","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021577277","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"28300407","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.38653809Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_COMM":"cardano-node","_UID":"10016","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system"} +{"__MONOTONIC_TIMESTAMP":"28300407","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=829;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=b17bd24fd1f73c5a","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.38666548Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":30,\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_UID":"10016","__SEQNUM":"2089","__REALTIME_TIMESTAMP":"1761317021577277","_HOSTNAME":"leios-node"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:41.386708223Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_GID":"10016","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__SEQNUM":"2090","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","__MONOTONIC_TIMESTAMP":"28300407","__REALTIME_TIMESTAMP":"1761317021577277","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82a;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=1f591e59a324f6c0"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021577277","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82b;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=ed6dab4b402f02ae","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.386743144Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM":"2091","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28300407","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__REALTIME_TIMESTAMP":"1761317021577277","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.386801531Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"blockNo\":32,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":580},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82c;b=082ebd52b7694299b9566558b64d809c;m=1afd477;t=641e89368703d;x=da5f3ab75bbd56ed","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28300407","_PID":"759","__SEQNUM":"2092","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_COMM":"cardano-node"} +{"_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82d;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=4443ac8dfbb9bc3","__SEQNUM":"2093","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__MONOTONIC_TIMESTAMP":"28395159","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.393051208Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":580},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317021672031","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_CAP_EFFECTIVE":"0","_GID":"10016","__MONOTONIC_TIMESTAMP":"28395159","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317021672031","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.441281919Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"Point\",\"slot\":487},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__SEQNUM":"2094","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82e;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=621df1f629b56e4a","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317021672031","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28395159","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.484080934Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2095","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=82f;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=7d80b85437d229a6"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=830;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=350a67989531c22f","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__SEQNUM":"2096","_CAP_EFFECTIVE":"0","PRIORITY":"6","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__REALTIME_TIMESTAMP":"1761317021672031","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.48499362Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":357}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"28395159","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node"} +{"_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=831;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=d0e4f5b9580cc3e2","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2097","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"28395159","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317021672031","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.420441561Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"BlockPoint\",\"slot\":397},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.485183309Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995@397\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2098","__REALTIME_TIMESTAMP":"1761317021672031","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_TRANSPORT":"stdout","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=832;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=35c2c5470d7ee918","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28395159","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=833;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=146e988aefe8bf58","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.524605079Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"delay\":1363920.44115844,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28395159","__REALTIME_TIMESTAMP":"1761317021672031","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2099","PRIORITY":"6","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0"} +{"SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_PID":"759","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=834;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=bd06542a1c2b9905","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2100","__MONOTONIC_TIMESTAMP":"28395159","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.524717104Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317021672031"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2101","_COMM":"cardano-node","_PID":"759","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021672031","_UID":"10016","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.524773815Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28395159","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=835;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=ec6b23d6415ec303","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6"} +{"__REALTIME_TIMESTAMP":"1761317021672031","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28395159","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=836;b=082ebd52b7694299b9566558b64d809c;m=1b14697;t=641e89369e25f;x=54861f4a48f8d943","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.544632205Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2102","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28451281","_TRANSPORT":"stdout","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.544706796Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__SEQNUM":"2103","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=837;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=a9a4129fcef7f006","__REALTIME_TIMESTAMP":"1761317021728154"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:41.56061608Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2104","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=838;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=9a80d2b521ca9e5a","__REALTIME_TIMESTAMP":"1761317021728154","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28451281","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__SEQNUM":"2105","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.560680055Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"Point\",\"slot\":444},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"28451281","_RUNTIME_SCOPE":"system","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=839;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=4ea8bdd34055092f","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021728154"} +{"_PID":"759","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83a;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=4e19c731eb733e17","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.593872821Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":251888120,\"CentiBlkIO\":0,\"CentiCpu\":101,\"CentiGC\":2,\"CentiMut\":92,\"FsRd\":50872320,\"FsWr\":200704,\"GcsMajor\":2,\"GcsMinor\":6,\"Heap\":49283072,\"Live\":4046480,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021728154","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2106","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"28451281","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_COMM":"cardano-node","_HOSTNAME":"leios-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.594286002Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2107","_PID":"759","__MONOTONIC_TIMESTAMP":"28451281","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83b;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=e2b4b416f218f3c3","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021728154","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28451281","_HOSTNAME":"leios-node","_PID":"759","PRIORITY":"6","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.594341875Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2108","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021728154","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83c;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=834ca277307cba53","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317021728154","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2109","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83d;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=5aa832363c023976","__MONOTONIC_TIMESTAMP":"28451281","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CAP_EFFECTIVE":"0","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.594597773Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83e;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=5764553229ca33c9","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.63330381Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"BlockPoint\",\"slot\":362},\"head\":{\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"BlockPoint\",\"slot\":397}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021728154","_HOSTNAME":"leios-node","__SEQNUM":"2110","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_GID":"10016","__MONOTONIC_TIMESTAMP":"28451281","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service"} +{"__MONOTONIC_TIMESTAMP":"28451281","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM":"2111","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=83f;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=35ada435b9d181c3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021728154","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_UID":"10016","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.633343201Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"Point\",\"slot\":444},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021728154","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=840;b=082ebd52b7694299b9566558b64d809c;m=1b221d1;t=641e8936abd9a;x=60a35bd14f2ebd1f","_PID":"759","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28451281","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2112","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.633432597Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"28524977","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021801846","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.633456623Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2113","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=841;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=4bb88cb0d9e05b3a","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_PID":"759","__REALTIME_TIMESTAMP":"1761317021801846","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28524977","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=842;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=f9024ba15d33f52","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.721276723Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"BlockPoint\",\"slot\":444},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2114","_UID":"10016","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"PRIORITY":"6","_GID":"10016","_UID":"10016","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.721550221Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173@444\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2115","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=843;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=162a8d6ae11173e","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_PID":"759","__MONOTONIC_TIMESTAMP":"28524977","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317021801846","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021801846","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM":"2116","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"28524977","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.72166951Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=844;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=4232b9c0512ef48f","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_FACILITY":"3","__SEQNUM":"2117","__REALTIME_TIMESTAMP":"1761317021801846","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.72170918Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"Point\",\"slot\":487},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=845;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=77143a20341abdd5","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"28524977"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28524977","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.721834056Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"Point\",\"slot\":487},\"blockNo\":\"29\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=846;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=bca9bd3a3f01a8fc","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2118","__REALTIME_TIMESTAMP":"1761317021801846","_SYSTEMD_SLICE":"system.slice","_PID":"759","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=847;b=082ebd52b7694299b9566558b64d809c;m=1b341b1;t=641e8936bdd76;x=cef24024b7608959","__SEQNUM":"2119","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28524977","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317021801846","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.734402693Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":580},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_GID":"10016","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=848;b=082ebd52b7694299b9566558b64d809c;m=1b4066e;t=641e8936ca236;x=48d3b199d4e0b695","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28575342","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317021852214","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2120","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.800872873Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"a98a7f6041f5e4a10997a3468cb58ccda2d74584168dedce86042ea39377863c\",\"kind\":\"BlockPoint\",\"slot\":376},\"head\":{\"headerHash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"BlockPoint\",\"slot\":444}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_PID":"759"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317021863526","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__MONOTONIC_TIMESTAMP":"28586658","SYSLOG_FACILITY":"3","_GID":"10016","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.80103239Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"Point\",\"slot\":487},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=849;b=082ebd52b7694299b9566558b64d809c;m=1b432a2;t=641e8936cce66;x=75544f9ff98953b6","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2121","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.801110054Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","PRIORITY":"6","__SEQNUM":"2122","__REALTIME_TIMESTAMP":"1761317021863526","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84a;b=082ebd52b7694299b9566558b64d809c;m=1b432a2;t=641e8936cce66;x=464aa38e42d0b221","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28586658"} +{"SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM":"2123","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"28586658","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_PID":"759","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84b;b=082ebd52b7694299b9566558b64d809c;m=1b432a2;t=641e8936cce66;x=a32fa39353c738d6","__REALTIME_TIMESTAMP":"1761317021863526","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.80113827Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.802721152Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"9769d5e198c5d2142c01741ff86591f6f3b87d19146acec8449e95bfb615441e\",\"kind\":\"BlockPoint\",\"slot\":362}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84c;b=082ebd52b7694299b9566558b64d809c;m=1b432a2;t=641e8936cce66;x=60b354bbc2542ae7","SYSLOG_FACILITY":"3","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28586658","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317021863526","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM":"2124","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout"} +{"_HOSTNAME":"leios-node","_COMM":"cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2125","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84d;b=082ebd52b7694299b9566558b64d809c;m=1b432a2;t=641e8936cce66;x=1b8b9edc0260b57a","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.802790155Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":362}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317021863526","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28586658","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0"} +{"_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84e;b=082ebd52b7694299b9566558b64d809c;m=1b4c12c;t=641e8936d5cf0;x=99e721149abcff25","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"28623148","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.818133726Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021900016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2126","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28635769","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317021912582","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2127","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.818344367Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":31,\"headerHash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=84f;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=ea480937133cd2cb","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"28635769","__SEQNUM":"2128","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=850;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=138d2978c05a000d","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.818398005Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021912582"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2129","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.81844885Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__REALTIME_TIMESTAMP":"1761317021912582","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=851;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=53d88f4fdaa378cd","__MONOTONIC_TIMESTAMP":"28635769","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317021912582","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.818526513Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"blockNo\":33,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":581},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=852;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=d71f7efcf60cd94","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2130","__MONOTONIC_TIMESTAMP":"28635769","SYSLOG_FACILITY":"3","_PID":"759","PRIORITY":"6","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.827748635Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":376}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28635769","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317021912582","_PID":"759","__SEQNUM":"2131","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=853;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=90d2e51e91c99333","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__MONOTONIC_TIMESTAMP":"28635769","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=854;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=d0e5a55e7f926598","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.827813448Z\",\"ns\":\"Net.InboundGovernor.Local.MuxCleanExit\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"MuxCleanExit\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317021912582","__SEQNUM":"2132","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=855;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=fdca639f85a97ff7","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28635769","_GID":"10016","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.827847251Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2133","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","PRIORITY":"6","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317021912582"} +{"__SEQNUM":"2134","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"28635769","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.845764612Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021912582","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=856;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=84e7ba65d3b1d64"} +{"__REALTIME_TIMESTAMP":"1761317021912582","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=857;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=89fe66c4cb811837","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_RUNTIME_SCOPE":"system","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28635769","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2135","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.851619825Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__SEQNUM":"2136","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.860581579Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317021912582","_UID":"10016","__MONOTONIC_TIMESTAMP":"28635769","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=858;b=082ebd52b7694299b9566558b64d809c;m=1b4f279;t=641e8936d8e06;x=b07f6a7776448caa","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.860691649Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__SEQNUM":"2137","__MONOTONIC_TIMESTAMP":"28703146","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317021980018","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=859;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=c41b030bf2350249","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"28703146","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_PID":"759","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.884520375Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionCleanup\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@1\"},\"kind\":\"ConnectionCleanup\"},\"sev\":\"Debug\",\"thread\":\"85\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85a;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=2f67f33b0477a048","__SEQNUM":"2138","_TRANSPORT":"stdout","_COMM":"cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317021980018","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__REALTIME_TIMESTAMP":"1761317021980018","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85b;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=b4ad97d76adac9f2","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__MONOTONIC_TIMESTAMP":"28703146","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_HOSTNAME":"leios-node","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM":"2139","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.884619271Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":0,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"85\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0"} +{"_GID":"10016","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.88475588Z\",\"ns\":\"Net.PeerSelection.Selection.GovernorWakeup\",\"data\":{\"kind\":\"GovernorWakeup\"},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317021980018","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28703146","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2140","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85c;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=8ed52d4aa487e8b0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_PID":"759","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2141","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85d;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=7ee0515c76595b94","_GID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28703146","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.90783535Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317021980018","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759"} +{"_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.910222804Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsRequest\",\"data\":{\"kind\":\"PublicRootsRequest\",\"numberOfRootPeers\":1,\"targetNumberOfRootPeers\":60},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85e;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=bf544cef8c0e72ab","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317021980018","_RUNTIME_SCOPE":"system","PRIORITY":"6","__SEQNUM":"2142","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_UID":"10016","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28703146","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2143","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.934466947Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":32,\"headerHash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317021980018","PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"28703146","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=85f;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=e8b8823dacc34b1","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM":"2144","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","PRIORITY":"6","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=860;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=747ac8c632776eda","__REALTIME_TIMESTAMP":"1761317021980018","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.934973715Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28703146","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317021980018","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=861;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=ef43be6fec016123","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.947452955Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__SEQNUM":"2145","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28703146","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=862;b=082ebd52b7694299b9566558b64d809c;m=1b5f9aa;t=641e8936e9572;x=9e84fb34a90ac305","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__MONOTONIC_TIMESTAMP":"28703146","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.955119851Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_GID":"10016","__REALTIME_TIMESTAMP":"1761317021980018","__SEQNUM":"2146","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__SEQNUM":"2147","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.955439445Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"Point\",\"slot\":580},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28769323","__REALTIME_TIMESTAMP":"1761317022046196","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=863;b=082ebd52b7694299b9566558b64d809c;m=1b6fc2b;t=641e8936f97f4;x=f9729ee16bbc0ede","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0"} +{"__REALTIME_TIMESTAMP":"1761317022046196","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=864;b=082ebd52b7694299b9566558b64d809c;m=1b6fc2b;t=641e8936f97f4;x=ae1b144f816e0430","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM":"2148","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28769323","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.955642543Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__SEQNUM":"2149","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=865;b=082ebd52b7694299b9566558b64d809c;m=1b6fc2b;t=641e8936f97f4;x=31a0b6cf71dcf986","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28769323","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022046196","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.955803457Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"BlockPoint\",\"slot\":487},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=866;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=f079298172c888db","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.992305583Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"blockNo\":34,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":588},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_UID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28788360","_PID":"759","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317022065230","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__SEQNUM":"2150","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.999682498Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_PID":"759","_GID":"10016","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2151","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317022065230","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"28788360","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=867;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=1139ce6c0d505cb8","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28788360","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:41.999732784Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":59},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM":"2152","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=868;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=3c09d99313cb202c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__REALTIME_TIMESTAMP":"1761317022065230","_TRANSPORT":"stdout","_HOSTNAME":"leios-node"} +{"_UID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM":"2153","_GID":"10016","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.000158536Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":28.723239436,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022065230","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"28788360","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=869;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=9300dc98dca525e1","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__REALTIME_TIMESTAMP":"1761317022065230","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.000185634Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86a;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=88ed145d84554e1a","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_TRANSPORT":"stdout","_GID":"10016","__MONOTONIC_TIMESTAMP":"28788360","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2154"} +{"PRIORITY":"6","__MONOTONIC_TIMESTAMP":"28788360","_UID":"10016","_CAP_EFFECTIVE":"0","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022065230","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86b;b=082ebd52b7694299b9566558b64d809c;m=1b74688;t=641e8936fe24e;x=1b8101244daf5889","_SYSTEMD_SLICE":"system.slice","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.000586803Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2155"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"28822702","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86c;b=082ebd52b7694299b9566558b64d809c;m=1b7ccae;t=641e893706863;x=20b27133c14435ea","PRIORITY":"6","_PID":"759","__REALTIME_TIMESTAMP":"1761317022099555","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2156","_UID":"10016","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.012800646Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":29,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":487,\"tieBreakVRF\":\"a7e63d9334cbd147ca4aec8bd508ad066926e1b271ecadf7db62f4da656c363a975d39d271cc9e5c348059e68c06828e0874f2c7cf10a7722b4cf47e7ff9dc75\"},\"newtip\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487\",\"oldTipSelectView\":{\"chainLength\":28,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":444,\"tieBreakVRF\":\"d0528b9adbe9af3a38bde9aed67fbb6dce6d4b7f50030540cb27e852115c9c1559b471d420a3925f504b5e8a471fec01a5a20768e30345c3c3dd3848e0f142c0\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86d;b=082ebd52b7694299b9566558b64d809c;m=1b813a3;t=641e89370af6b;x=f5ffe6b8c0fefae8","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.012251973Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"91\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317022117739","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"28840867","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__SEQNUM":"2157","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6"} +{"__SEQNUM":"2158","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.040475951Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86e;b=082ebd52b7694299b9566558b64d809c;m=1b829c2;t=641e89370c56a;x=c2cf9edff9826ef1","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"28846530","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022123370","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=86f;b=082ebd52b7694299b9566558b64d809c;m=1b847f5;t=641e89370e3a9;x=e59122b6c1ee00e2","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.040571494Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":33,\"headerHash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28854261","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2159","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_COMM":"cardano-node","_PID":"759","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022131113","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28864069","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.040605576Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__REALTIME_TIMESTAMP":"1761317022140940","SYSLOG_FACILITY":"3","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=870;b=082ebd52b7694299b9566558b64d809c;m=1b86e45;t=641e893710a0c;x=b731ef5acfdca947","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2160","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317022140940","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_UID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=871;b=082ebd52b7694299b9566558b64d809c;m=1b86e45;t=641e893710a0c;x=7610ec58c2ac6614","__MONOTONIC_TIMESTAMP":"28864069","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2161","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.040632395Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=872;b=082ebd52b7694299b9566558b64d809c;m=1b8a36b;t=641e893713f33;x=8412bb0aa4738117","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022154547","_UID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM":"2162","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.040675697Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"blockNo\":35,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":602},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28877675","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=873;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=a848bdf816d7c2cf","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","__SEQNUM":"2163","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28889451","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.056243597Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"91\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022166305","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.082049391Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28889451","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022166305","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=874;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=fcb0ac5defbf96b9","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_GID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2164"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317022166305","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=875;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=b867c0b211efb681","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_PID":"759","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"28889451","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2165","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.082104985Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_COMM":"cardano-node","PRIORITY":"6","_PID":"759","__SEQNUM":"2166","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=876;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=bdd3a6e28248ce72","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.083343689Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336@487\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"28889451","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317022166305","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__SEQNUM":"2167","_UID":"10016","_GID":"10016","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.083452083Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"28889451","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=877;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=22e6ffd20aa1c87a","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022166305","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_HOSTNAME":"leios-node","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2168","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=878;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=d6d055e06dbc9dd","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28889451","__REALTIME_TIMESTAMP":"1761317022166305","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.083492032Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"Point\",\"slot\":505},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM":"2169","_RUNTIME_SCOPE":"system","_UID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317022166305","__MONOTONIC_TIMESTAMP":"28889451","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.130312508Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=879;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=921532ca388c91ff","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_GID":"10016"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022166305","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_UID":"10016","_PID":"759","__MONOTONIC_TIMESTAMP":"28889451","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.130581257Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsResults\",\"data\":{\"diffTime\":4,\"group\":2,\"kind\":\"PublicRootsResults\",\"result\":{\"bigLedgerPeers\":[],\"bootstrapPeers\":[],\"kind\":\"PublicRootPeers\",\"ledgerPeers\":[],\"publicConfigPeers\":[]}},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2170","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87a;b=082ebd52b7694299b9566558b64d809c;m=1b8d16b;t=641e893716d21;x=71f67d43e1287b8d"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2171","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022218733","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.132594083Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_GID":"10016","__MONOTONIC_TIMESTAMP":"28941860","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87b;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=57a080f0292ba902","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_PID":"759","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28941860","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2172","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.132746337Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":34,\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87c;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=196a02bf9f344f57","__REALTIME_TIMESTAMP":"1761317022218733","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2173","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317022218733","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.132800813Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"28941860","_TRANSPORT":"stdout","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87d;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=5412158a63d8b1c9","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"28941860","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.132842439Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_GID":"10016","__REALTIME_TIMESTAMP":"1761317022218733","PRIORITY":"6","_HOSTNAME":"leios-node","__SEQNUM":"2174","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87e;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=38aece4dfb1ee9ea","SYSLOG_FACILITY":"3"} +{"__REALTIME_TIMESTAMP":"1761317022218733","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=87f;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=c3f100a1c4335ed6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.147589285Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"28941860","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__SEQNUM":"2175","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"28941860","__SEQNUM":"2176","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.163145452Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"b7c2df0c25cf6528ae9237915142496974c4f07c1ad15d3b7563fa7491badfb3\",\"kind\":\"BlockPoint\",\"slot\":392},\"head\":{\"headerHash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"BlockPoint\",\"slot\":487}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=880;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=140d2d0956722eb5","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022218733","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.163215014Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"Point\",\"slot\":505},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__SEQNUM":"2177","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022218733","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=881;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=cc17ab53627ede5e","PRIORITY":"6","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28941860"} +{"_UID":"10016","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__SEQNUM":"2178","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"28941860","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022218733","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=882;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=6e10c4b8768a2040","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.163292677Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=883;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=7ebb06e225105c9f","__MONOTONIC_TIMESTAMP":"28941860","PRIORITY":"6","SYSLOG_FACILITY":"3","_PID":"759","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.163320055Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2179","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022218733","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=884;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=4d2929648e191fa8","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022218733","__MONOTONIC_TIMESTAMP":"28941860","__SEQNUM":"2180","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.178356324Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2181","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.178742127Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"delay\":1363827.178501035,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022218733","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"28941860","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=885;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=817faf607e5f7ff","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","PRIORITY":"6","_GID":"10016","_UID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=886;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=650010dde2eebbf2","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"28941860","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.178821187Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022218733","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2182","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_UID":"10016","_PID":"759","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022218733","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=887;b=082ebd52b7694299b9566558b64d809c;m=1b99e24;t=641e8937239ed;x=3a233e2259a5cd99","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.178856946Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2183","_COMM":"cardano-node","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"28941860","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__REALTIME_TIMESTAMP":"1761317022301297","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29024427","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2184","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=888;b=082ebd52b7694299b9566558b64d809c;m=1bae0ab;t=641e893737c71;x=ef2ada8821c82c39","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.230240292Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"blockNo\":36,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":707},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node"} +{"_HOSTNAME":"leios-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=889;b=082ebd52b7694299b9566558b64d809c;m=1bae0ab;t=641e893737c71;x=3eaa7c55eb7d5173","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.230423276Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":707},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022301297","__MONOTONIC_TIMESTAMP":"29024427","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2185","_PID":"759","_SYSTEMD_SLICE":"system.slice"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2186","__REALTIME_TIMESTAMP":"1761317022318024","PRIORITY":"6","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88a;b=082ebd52b7694299b9566558b64d809c;m=1bb21ff;t=641e89373bdc8;x=22a23fcbc1c02448","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.198289025Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_PID":"759","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29041151","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.26263128Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"BlockPoint\",\"slot\":505},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29041151","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88b;b=082ebd52b7694299b9566558b64d809c;m=1bb21ff;t=641e89373bdc8;x=705c4bc2c7531d11","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__SEQNUM":"2187","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022318024","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"29041151","_UID":"10016","PRIORITY":"6","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.262799179Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57@505\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022318024","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2188","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88c;b=082ebd52b7694299b9566558b64d809c;m=1bb21ff;t=641e89373bdc8;x=f5c0543fc4a3c26","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2189","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022318024","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.282606166Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":392}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"29041151","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88d;b=082ebd52b7694299b9566558b64d809c;m=1bb21ff;t=641e89373bdc8;x=6ba21ad5357a0109","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_UID":"10016","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2190","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.329542578Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"29066428","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88e;b=082ebd52b7694299b9566558b64d809c;m=1bb84bc;t=641e89374207e;x=6c5632cce80b00f","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022343294","_PID":"759","_GID":"10016","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317022347954","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.329593422Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"Point\",\"slot\":558},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2191","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=88f;b=082ebd52b7694299b9566558b64d809c;m=1bb96eb;t=641e8937432b2;x=dcb803f77a7b9406","_SYSTEMD_SLICE":"system.slice","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29071083","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_HOSTNAME":"leios-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317022359573","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.3296912Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"Point\",\"slot\":558},\"blockNo\":\"31\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29082704","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_PID":"759","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=890;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=def2b9bd82cc00a7","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2192","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=891;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=798e4beb7ede1c26","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29082704","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2193","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022359573","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.341713119Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"BlockPoint\",\"slot\":397},\"head\":{\"headerHash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"BlockPoint\",\"slot\":505}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29082704","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=892;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=c2885a4f214714aa","__REALTIME_TIMESTAMP":"1761317022359573","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2194","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.341772065Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"Point\",\"slot\":558},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6"} +{"_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","PRIORITY":"6","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29082704","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.341855875Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022359573","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2195","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=893;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=e590f85e505ba77d","_CAP_EFFECTIVE":"0"} +{"_PID":"759","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2196","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.342818567Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"521f832c0107436ec12d73e11b8aa2061b3fa531eadcf0b767ac7f524c856995\",\"kind\":\"BlockPoint\",\"slot\":397}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"29082704","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317022359573","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_TRANSPORT":"stdout","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=894;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=eb560ad7accaa376"} +{"_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29082704","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_PID":"759","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.342923329Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":397}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022359573","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=895;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=55ab37d21fbdd136","__SEQNUM":"2197","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service"} +{"_PID":"759","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM":"2198","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=896;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=4c1c1c2b7ba1bfc8","_TRANSPORT":"stdout","PRIORITY":"6","_UID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.353577756Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29082704","__REALTIME_TIMESTAMP":"1761317022359573"} +{"PRIORITY":"6","_GID":"10016","__MONOTONIC_TIMESTAMP":"29082704","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","__SEQNUM":"2199","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=897;b=082ebd52b7694299b9566558b64d809c;m=1bbc450;t=641e893746015;x=810bd5fe6d277b17","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317022359573","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.356284245Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=898;b=082ebd52b7694299b9566558b64d809c;m=1bc9247;t=641e893752e0d;x=8c3023c99ccc72c3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317022412301","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.358721705Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"BlockPoint\",\"slot\":558},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__MONOTONIC_TIMESTAMP":"29135431","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2200","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2201","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022412301","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=899;b=082ebd52b7694299b9566558b64d809c;m=1bc9247;t=641e893752e0d;x=fc0fc0474006531d","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.374354139Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29135431","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_COMM":"cardano-node","PRIORITY":"6"} +{"PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89a;b=082ebd52b7694299b9566558b64d809c;m=1bc9247;t=641e893752e0d;x=eb465d65c6877088","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2202","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022412301","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.374587968Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":707},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29135431","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89b;b=082ebd52b7694299b9566558b64d809c;m=1bc9247;t=641e893752e0d;x=75f1abf52356e3da","_COMM":"cardano-node","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_PID":"759","__MONOTONIC_TIMESTAMP":"29135431","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317022412301","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.380849099Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab@558\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2203","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__REALTIME_TIMESTAMP":"1761317022440515","_TRANSPORT":"stdout","__SEQNUM":"2204","__MONOTONIC_TIMESTAMP":"29163644","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89c;b=082ebd52b7694299b9566558b64d809c;m=1bd007c;t=641e893759c43;x=14755c7e77530ca2","_SYSTEMD_SLICE":"system.slice","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.437156255Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89d;b=082ebd52b7694299b9566558b64d809c;m=1bd18d8;t=641e89375b49e;x=d1cab4475996951b","__MONOTONIC_TIMESTAMP":"29169880","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_PID":"759","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317022446750","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__SEQNUM":"2205","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.437202909Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"Point\",\"slot\":580},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_GID":"10016","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29176071","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.437507976Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"12ab6ce0148ac84361124591b1fdfe53eb9d5f0f6ddd5333b1fe64506f045173\",\"kind\":\"BlockPoint\",\"slot\":444},\"head\":{\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"BlockPoint\",\"slot\":558}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2206","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317022452943","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89e;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=59acaa2e3e9a48f5","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=89f;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=d263b818ce165a5d","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.437559379Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"Point\",\"slot\":580},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29176071","__REALTIME_TIMESTAMP":"1761317022452943","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2207","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_UID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022452943","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a0;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=f7cf8738b9ef41fe","_GID":"10016","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.437634807Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM":"2208","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__MONOTONIC_TIMESTAMP":"29176071","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.4376647Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_GID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29176071","__SEQNUM":"2209","__REALTIME_TIMESTAMP":"1761317022452943","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a1;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=75281ca36b1f8a1a","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_COMM":"cardano-node","_HOSTNAME":"leios-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a2;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=95f67cb64bc936c7","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29176071","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.438553081Z\",\"ns\":\"Net.Server.Local.AcceptConnection\",\"data\":{\"address\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"AcceptConnection\"},\"sev\":\"Debug\",\"thread\":\"48\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM":"2210","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__REALTIME_TIMESTAMP":"1761317022452943","_SYSTEMD_SLICE":"system.slice","_PID":"759"} +{"PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__REALTIME_TIMESTAMP":"1761317022452943","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.438703658Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":444}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__SEQNUM":"2211","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a3;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=914f0d0d56b50376","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29176071","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016"} +{"_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29176071","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a4;b=082ebd52b7694299b9566558b64d809c;m=1bd3107;t=641e89375cccf;x=f90b11afc3d88612","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__SEQNUM":"2212","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022452943","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.439395366Z\",\"ns\":\"Net.ConnectionManager.Local.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Inbound\",\"remoteAddress\":{\"path\":\"/run/cardano-node/node.socket@2\"}},\"sev\":\"Debug\",\"thread\":\"92\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022493209","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29216336","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:41.420441561 UTC to 2025-10-24 14:43:42.446355189 UTC","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a5;b=082ebd52b7694299b9566558b64d809c;m=1bdce50;t=641e893766a19;x=dff60d8ea4e5c025","__SEQNUM":"2213","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2214","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29220085","PRIORITY":"6","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317022496956","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_GID":"10016","_CAP_EFFECTIVE":"0","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.439546782Z\",\"ns\":\"Net.Handshake.Local.Receive.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@2\\\"}\",\"event\":\"Recv AnyMessage MsgProposeVersions (fromList [(NodeToClientV_16,TList [TInt 42,TBool False]),(NodeToClientV_17,TList [TInt 42,TBool False]),(NodeToClientV_18,TList [TInt 42,TBool False]),(NodeToClientV_19,TList [TInt 42,TBool False]),(NodeToClientV_20,TList [TInt 42,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"93\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a6;b=082ebd52b7694299b9566558b64d809c;m=1bddcf5;t=641e8937678bc;x=63d1f77ff0deede8","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_PID":"759","__SEQNUM":"2215","PRIORITY":"6","_UID":"10016","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317022511692","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a7;b=082ebd52b7694299b9566558b64d809c;m=1be1687;t=641e89376b24c;x=7503c2f3dbe0b76","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.440382084Z\",\"ns\":\"Net.Handshake.Local.Send.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@2\\\"}\",\"event\":\"Send AnyMessage MsgAcceptVersion NodeToClientV_20 (TList [TInt 42,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"93\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"29234823","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29242870","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.440406109Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"networkMagic\":42,\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":20},\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"93\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2216","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a8;b=082ebd52b7694299b9566558b64d809c;m=1be35f6;t=641e89376d1af;x=6ccdfc6e61734b8f","__REALTIME_TIMESTAMP":"1761317022519727"} +{"_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29252071","__REALTIME_TIMESTAMP":"1761317022528942","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8a9;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=48c4436d234ecb96","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.440451367Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"92\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2217","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_PID":"759"} +{"__SEQNUM":"2218","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022528942","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"29252071","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.44047204Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"92\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_GID":"10016","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8aa;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=dbd59d2d4362b514","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_PID":"759","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317022528942","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ab;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=58bab85c02e52d18","__SEQNUM":"2219","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.445754554Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29252071","PRIORITY":"6","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.445860713Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":35,\"headerHash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022528942","_COMM":"cardano-node","__SEQNUM":"2220","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"29252071","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","PRIORITY":"6","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ac;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=7e6c87bd92bc3c0f","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__REALTIME_TIMESTAMP":"1761317022528942","_UID":"10016","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2221","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ad;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=ff464fc3738e3aca","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.446323342Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"29252071","_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016"} +{"__REALTIME_TIMESTAMP":"1761317022528942","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.446355189Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_UID":"10016","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ae;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=ff02a16d43f40ea3","__SEQNUM":"2222","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__MONOTONIC_TIMESTAMP":"29252071","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8af;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=bd8be2c6d9c0ecbc","_GID":"10016","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"29252071","PRIORITY":"6","__SEQNUM":"2223","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317022528942","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.472782291Z\",\"ns\":\"Net.InboundGovernor.Local.NewConnection\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"NewConnection\",\"provenance\":\"Inbound\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022528942","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29252071","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM":"2224","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.472981758Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b0;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=4892fd7eee5969a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759"} +{"SYSLOG_FACILITY":"3","__SEQNUM":"2225","__REALTIME_TIMESTAMP":"1761317022528942","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_UID":"10016","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__MONOTONIC_TIMESTAMP":"29252071","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b1;b=082ebd52b7694299b9566558b64d809c;m=1be59e7;t=641e89376f5ae;x=b37e843240b112c3","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.473046291Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}"} +{"_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__SEQNUM":"2226","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b2;b=082ebd52b7694299b9566558b64d809c;m=1bf1a6c;t=641e89377b635;x=715c25b3b0ba897e","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022578229","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"29301356","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.44641218Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"blockNo\":37,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":710},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022578229","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.480422927Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b3;b=082ebd52b7694299b9566558b64d809c;m=1bf1a6c;t=641e89377b635;x=4b180d0b49aecf86","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"29301356","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2227","_GID":"10016","_COMM":"cardano-node","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.496434459Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"BlockPoint\",\"slot\":580},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29301356","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b4;b=082ebd52b7694299b9566558b64d809c;m=1bf1a6c;t=641e89377b635;x=c3c8c36c32b18ecf","_PID":"759","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022578229","__SEQNUM":"2228","SYSLOG_FACILITY":"3","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"__REALTIME_TIMESTAMP":"1761317022578229","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2229","__MONOTONIC_TIMESTAMP":"29301356","_UID":"10016","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b5;b=082ebd52b7694299b9566558b64d809c;m=1bf1a6c;t=641e89377b635;x=33d03867cc77908a","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.507146156Z\",\"ns\":\"StateQueryServer.Receive.Acquire\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgAcquire\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_GID":"10016","PRIORITY":"6","_PID":"759"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2230","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317022578229","_COMM":"cardano-node","PRIORITY":"6","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b6;b=082ebd52b7694299b9566558b64d809c;m=1bf1a6c;t=641e89377b635;x=75a47133dcb7e966","__MONOTONIC_TIMESTAMP":"29301356","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.50863182Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"29330996","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317022607858","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.508748874Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":36,\"headerHash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_GID":"10016","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b7;b=082ebd52b7694299b9566558b64d809c;m=1bf8e34;t=641e8937829f2;x=6c5425d84a22b199","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2231"} +{"_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.508791896Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b8;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=1920414e6cd8688d","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","__SEQNUM":"2232","__REALTIME_TIMESTAMP":"1761317022614941","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29338071","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__MONOTONIC_TIMESTAMP":"29338071","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022614941","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.508829889Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2233","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8b9;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=3987f3e907ea64ad","_SYSTEMD_SLICE":"system.slice"} +{"__MONOTONIC_TIMESTAMP":"29338071","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317022614941","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.509640328Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ba;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=107ff653be608d4b","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__SEQNUM":"2234","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2235","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.510977928Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"blockNo\":38,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":728},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8bb;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=4c0de2913a0baa0c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__MONOTONIC_TIMESTAMP":"29338071","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022614941","_GID":"10016","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"29338071","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022614941","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.518771376Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","__SEQNUM":"2236","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8bc;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=cd5ae6b7f5f59def"} +{"__SEQNUM":"2237","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.518844849Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8bd;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=5ee25143f2f59478","__REALTIME_TIMESTAMP":"1761317022614941","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"29338071","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_GID":"10016","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_COMM":"cardano-node","__SEQNUM":"2238","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.519359161Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb@580\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8be;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=3856902451955121","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"29338071","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022614941","_PID":"759","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2239","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29338071","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8bf;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=b60e077cecc393c3","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.519428723Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317022614941","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c0;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=f966e39085c7bfff","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022614941","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29338071","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.519452469Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"Point\",\"slot\":581},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2240","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_UID":"10016","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317022614941","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c1;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=9a42aa2c75a9504a","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.526707301Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":487}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29338071","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM":"2241","_COMM":"cardano-node"} +{"_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__MONOTONIC_TIMESTAMP":"29338071","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2242","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c2;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=abf640d3c6a03d03","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022614941","_GID":"10016","PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.539724319Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"2720251bb2d73b8d32056469750a3a9485d56d6eba7cdacdafd470983bdef336\",\"kind\":\"BlockPoint\",\"slot\":487},\"head\":{\"headerHash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"BlockPoint\",\"slot\":580}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_GID":"10016","__REALTIME_TIMESTAMP":"1761317022614941","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29338071","PRIORITY":"6","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.539792484Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"Point\",\"slot\":581},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c3;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=6754264213784b","_PID":"759","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2243","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.539928255Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022614941","__SEQNUM":"2244","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c4;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=54f3ecf1fdd8820e","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29338071","_PID":"759","_GID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c5;b=082ebd52b7694299b9566558b64d809c;m=1bfa9d7;t=641e89378459d;x=949484de51204b1d","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__REALTIME_TIMESTAMP":"1761317022614941","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29338071","_COMM":"cardano-node","_PID":"759","__SEQNUM":"2245","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.539963735Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_RUNTIME_SCOPE":"system","_GID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_HOSTNAME":"leios-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c6;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=30c15931f7d56971","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29417908","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__SEQNUM":"2246","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540031062Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022694777"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022694777","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"29417908","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c7;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=b8fc50f9eb3d9124","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540056205Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToWarmRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"PromotedToWarmRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundIdleSt\"}}},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__SEQNUM":"2247","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c8;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=7401e3340fa75cbd","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540087773Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":1},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29417908","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__SEQNUM":"2248","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022694777","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022694777","__SEQNUM":"2249","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8c9;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=8a193f81e627104f","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29417908","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.54011962Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"RemoteWarmSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_GID":"10016","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2250","__REALTIME_TIMESTAMP":"1761317022694777","_PID":"759","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ca;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=1c40272086be554","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540191697Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToHotRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"PromotedToHotRemote\"},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29417908","_COMM":"cardano-node","_GID":"10016"} +{"_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022694777","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540219913Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":1,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_PID":"759","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29417908","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8cb;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=73b4924f1316d474","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2251","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540274389Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"RemoteHotSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","__MONOTONIC_TIMESTAMP":"29417908","__REALTIME_TIMESTAMP":"1761317022694777","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2252","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8cc;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=cfa930e68339137a","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_GID":"10016","__REALTIME_TIMESTAMP":"1761317022694777","__MONOTONIC_TIMESTAMP":"29417908","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8cd;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=ee0972e938ee381","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2253","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","PRIORITY":"6","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540420776Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022694777","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ce;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=b20b34a8b34f2817","__SEQNUM":"2254","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540539786Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":37,\"headerHash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"29417908","_SYSTEMD_SLICE":"system.slice"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.54058197Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8cf;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=8e642b968b03af59","__REALTIME_TIMESTAMP":"1761317022694777","_UID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"29417908","__SEQNUM":"2255","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM":"2256","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540618567Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"29417908","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317022694777","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d0;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=659189a696c9a8ad","_TRANSPORT":"stdout"} +{"_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM":"2257","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022694777","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d1;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=80585e1138189ebc","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29417908","_UID":"10016","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.540676674Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"blockNo\":39,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":740},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"__SEQNUM":"2258","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.588614052Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d2;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=d73d80653757d889","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317022694777","__MONOTONIC_TIMESTAMP":"29417908","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_COMM":"cardano-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__SEQNUM":"2259","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.588696185Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":38,\"headerHash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022694777","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d3;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=8e007f218f967e60","__MONOTONIC_TIMESTAMP":"29417908","_CAP_EFFECTIVE":"0","_PID":"759","_UID":"10016"} +{"__SEQNUM":"2260","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29417908","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d4;b=082ebd52b7694299b9566558b64d809c;m=1c0e1b4;t=641e893797d79;x=c8d31875092b0ed1","_PID":"759","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317022694777","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.588727474Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d5;b=082ebd52b7694299b9566558b64d809c;m=1c23a63;t=641e8937ad62c;x=f868b86d43aaa48f","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2261","PRIORITY":"6","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.588753176Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022783020","__MONOTONIC_TIMESTAMP":"29506147"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:42.588811563Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"blockNo\":40,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":746},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d6;b=082ebd52b7694299b9566558b64d809c;m=1c25271;t=641e8937aee37;x=e3e4705d158b04b3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__SEQNUM":"2262","_RUNTIME_SCOPE":"system","PRIORITY":"6","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317022789175","__MONOTONIC_TIMESTAMP":"29512305","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2263","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.606181927Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d7;b=082ebd52b7694299b9566558b64d809c;m=1c26abc;t=641e8937b0681;x=37753b2a2f96d894","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317022795393","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29518524","_RUNTIME_SCOPE":"system"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d8;b=082ebd52b7694299b9566558b64d809c;m=1c286db;t=641e8937b229e;x=d59df9797b1653a6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM":"2264","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__MONOTONIC_TIMESTAMP":"29525723","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022802590","_GID":"10016","_UID":"10016","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.606495654Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout"} +{"_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29535094","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022811965","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.60657667Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2265","_UID":"10016","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8d9;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=24e74671d586001e","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_PID":"759","_SYSTEMD_SLICE":"system.slice"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.629127581Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2266","_PID":"759","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__MONOTONIC_TIMESTAMP":"29535094","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8da;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=72f3914ee4c38dec","__REALTIME_TIMESTAMP":"1761317022811965","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2267","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.629351073Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"Point\",\"slot\":707},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317022811965","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29535094","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8db;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=e1d1f2b768f462f0"} +{"__REALTIME_TIMESTAMP":"1761317022811965","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8dc;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=c0d4c9c81a257e95","_GID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2268","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.629662565Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","PRIORITY":"6","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"29535094","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_PID":"759","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","PRIORITY":"6","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8dd;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=80636388a4a61b67","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2269","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"29535094","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.629708102Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317022811965","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"29535094","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8de;b=082ebd52b7694299b9566558b64d809c;m=1c2ab76;t=641e8937b473d;x=b7216a618c432162","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2270","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022811965","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.62976621Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service"} +{"__REALTIME_TIMESTAMP":"1761317022844714","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_PID":"759","_GID":"10016","_HOSTNAME":"leios-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.652598162Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"29567844","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8df;b=082ebd52b7694299b9566558b64d809c;m=1c32b64;t=641e8937bc72a;x=8d2e5bb9ca3029fb","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2271","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.652724435Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":39,\"headerHash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"2272","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","_GID":"10016","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__MONOTONIC_TIMESTAMP":"29574542","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e0;b=082ebd52b7694299b9566558b64d809c;m=1c3458e;t=641e8937be153;x=b52e1681d0d588c9","__REALTIME_TIMESTAMP":"1761317022851411"} +{"_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e1;b=082ebd52b7694299b9566558b64d809c;m=1c36135;t=641e8937bfcf9;x=ab72bcef98ca9cd5","__REALTIME_TIMESTAMP":"1761317022858489","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.652760473Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"29581621","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2273","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__MONOTONIC_TIMESTAMP":"29590110","__SEQNUM":"2274","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.652786733Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317022866979","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e2;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=d67ae4d25024e4d4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_PID":"759"} +{"_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e3;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=51d1f25dc30becd8","_UID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.652830873Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"blockNo\":41,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":756},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317022866979","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2275","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29590110","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_GID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM":"2276","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022866979","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_UID":"10016","_PID":"759","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.726709536Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29590110","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e4;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=ed0057ba1b189ea"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_PID":"759","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29590110","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2277","_GID":"10016","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e5;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=335596df979bde70","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317022866979","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.737302782Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system"} +{"_PID":"759","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e6;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=c7b65c7238b89794","_HOSTNAME":"leios-node","__SEQNUM":"2278","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317022866979","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29590110","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.749668599Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"BlockPoint\",\"slot\":581},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317022866979","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","__SEQNUM":"2279","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e7;b=082ebd52b7694299b9566558b64d809c;m=1c3825e;t=641e8937c1e23;x=b73f182cb86a2425","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29590110","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788189138Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":251888120,\"CentiBlkIO\":0,\"CentiCpu\":109,\"CentiGC\":2,\"CentiMut\":101,\"FsRd\":50872320,\"FsWr\":262144,\"GcsMajor\":2,\"GcsMinor\":6,\"Heap\":49283072,\"Live\":4046480,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"29629543","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2280","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317022906410","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e8;b=082ebd52b7694299b9566558b64d809c;m=1c41c67;t=641e8937cb82a;x=f2590e47ecee7766","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788546725Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_COMM":"cardano-node"} +{"_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__REALTIME_TIMESTAMP":"1761317022914130","__MONOTONIC_TIMESTAMP":"29637259","PRIORITY":"6","__SEQNUM":"2281","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8e9;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=389821ef25fd87b3","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788694788Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":40,\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node"} +{"__REALTIME_TIMESTAMP":"1761317022914130","__SEQNUM":"2282","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ea;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=9059d335f8f0fc90","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29637259","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788731385Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788757087Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29637259","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8eb;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=8421bf46d200a727","__REALTIME_TIMESTAMP":"1761317022914130","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM":"2283","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022914130","__MONOTONIC_TIMESTAMP":"29637259","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ec;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=3b654a75fc5685ae","_PID":"759","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM":"2284","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.788801785Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"blockNo\":42,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":780},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022914130","_RUNTIME_SCOPE":"system","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"29637259","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.801003057Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__SEQNUM":"2285","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ed;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=90d197d4c06623c0","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2286","_PID":"759","_COMM":"cardano-node","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ee;b=082ebd52b7694299b9566558b64d809c;m=1c43a8b;t=641e8937cd652;x=cf0826ebdad82e90","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317022914130","_UID":"10016","__MONOTONIC_TIMESTAMP":"29637259","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.802222206Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":780},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2287","__REALTIME_TIMESTAMP":"1761317022951386","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29674513","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_FACILITY":"3","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.802325292Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ef;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=a4abbfd205a860a3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317022951386","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.802373901Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2288","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f0;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=d5fe47bcef7d7c0b","__MONOTONIC_TIMESTAMP":"29674513","_UID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"29674513","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317022951386","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2289","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f1;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=cafca0b9a4133086","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.809504137Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9@581\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f2;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=ffe36760201c95f6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29674513","_SYSTEMD_SLICE":"system.slice","_PID":"759","_UID":"10016","__REALTIME_TIMESTAMP":"1761317022951386","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2290","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.809614207Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f3;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=7fda3fef6b6e55b1","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29674513","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__SEQNUM":"2291","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.809647731Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"Point\",\"slot\":588},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317022951386","_PID":"759","_UID":"10016"} +{"_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_COMM":"cardano-node","_UID":"10016","__SEQNUM":"2292","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f4;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=bff74dfe7aba0540","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.81102109Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":505}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317022951386","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29674513","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:42.828007606Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29674513","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2293","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f5;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=a362e98cbb4bec96","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317022951386","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_UID":"10016","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f6;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=66230282efcf2dfb","__REALTIME_TIMESTAMP":"1761317022951386","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","PRIORITY":"6","__SEQNUM":"2294","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29674513","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.82830513Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"delay\":1363680.828117397,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.828531974Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f7;b=082ebd52b7694299b9566558b64d809c;m=1c4cc11;t=641e8937d67da;x=7f568c533f71380d","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"29674513","__SEQNUM":"2295","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317022951386","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"29726349","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.828625003Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0206ad821a888a6e67e2ab6403bc3692066705f215e9299d73ab5319c2734c57\",\"kind\":\"BlockPoint\",\"slot\":505},\"head\":{\"headerHash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"BlockPoint\",\"slot\":581}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_GID":"10016","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f8;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=b05568631b6f5e4b","__SEQNUM":"2296","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node"} +{"__MONOTONIC_TIMESTAMP":"29726349","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317023003222","_UID":"10016","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8f9;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=d056a0cee7f490ec","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.857781223Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__SEQNUM":"2297","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023003222","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.865732233Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8fa;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=23a8898847795ee3","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2298","_COMM":"cardano-node","PRIORITY":"6","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"29726349","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system"} +{"_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.89098209Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"Point\",\"slot\":588},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2299","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8fb;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=f0511840784820c7","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29726349","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_PID":"759","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8fc;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=992ee093cf2e2ccc","_CAP_EFFECTIVE":"0","__SEQNUM":"2300","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.891086852Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023003222","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29726349","_GID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.891108922Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29726349","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2301","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8fd;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=7ab08c2c02fa4424","PRIORITY":"6","SYSLOG_FACILITY":"3","_PID":"759"} +{"_PID":"759","_TRANSPORT":"stdout","__SEQNUM":"2302","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"29726349","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8fe;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=18c0d4078d180ac4","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.89129023Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"29726349","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.906142676Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023003222","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=8ff;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=2a9445e5d019b7ea","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2303","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_GID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_PID":"759","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"29726349","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=900;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=f5f0f6c3332ac1d5","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","PRIORITY":"6","__SEQNUM":"2304","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.931279949Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023003222"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:42.956490137Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"BlockPoint\",\"slot\":588},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_SLICE":"system.slice","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"29726349","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=901;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=ae91b49c02f64dba","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__SEQNUM":"2305","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__SEQNUM":"2306","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023003222","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29726349","_GID":"10016","_TRANSPORT":"stdout","_PID":"759","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=902;b=082ebd52b7694299b9566558b64d809c;m=1c5968d;t=641e8937e3256;x=e1dc88f03fd8399b","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.956644346Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":34,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":588,\"tieBreakVRF\":\"2c378d8710efaab90d72652d042886ef8d1d4b1365d016c30267cebd038f2a77c1b6bcb7fd121ad12840541641b1f4c3ca21985b8847eebceb927c82be65018d\"},\"newtip\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588\",\"oldTipSelectView\":{\"chainLength\":33,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":581,\"tieBreakVRF\":\"1644595d7c72451ed3a68c93e6bdb8dc3cae8de72d3b609c254cd1d5064bdb8b10bfc31fb0a1c32190a5f511e443e650e27d57b04eb9dc92b082f29069b7573b\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"__SEQNUM":"2307","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"29808858","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=903;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=7effc46d08bd6f1c","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023085731","_UID":"10016","_COMM":"cardano-node","_HOSTNAME":"leios-node","_GID":"10016","PRIORITY":"6","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.956851635Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88@588\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"29808858","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=904;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=dfe1d547981f693a","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.957007521Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317023085731","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__SEQNUM":"2308","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.957035457Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"Point\",\"slot\":602},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","PRIORITY":"6","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29808858","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_UID":"10016","__SEQNUM":"2309","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=905;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=3cbb1c0d8a39f081","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023085731","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.957138264Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"Point\",\"slot\":602},\"blockNo\":\"35\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023085731","__SEQNUM":"2310","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=906;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=1a667c071f956e8b","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29808858","_PID":"759","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_COMM":"cardano-node"} +{"_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=907;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=cbacf2f811b78ece","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317023085731","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2311","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.99273357Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"BlockPoint\",\"slot\":558},\"head\":{\"headerHash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"BlockPoint\",\"slot\":588}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_PID":"759","__MONOTONIC_TIMESTAMP":"29808858"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"29808858","__REALTIME_TIMESTAMP":"1761317023085731","_PID":"759","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.992791399Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"Point\",\"slot\":602},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=908;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=10d76250d731cdc6","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM":"2312"} +{"_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=909;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=13fd6dc2435e58dd","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2313","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023085731","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29808858","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.022697155Z\",\"ns\":\"StateQueryServer.Receive.Release\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgRelease\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_PID":"759"} +{"_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2314","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29808858","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90a;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=b05f839aac4be3cc","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023085731","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.022746323Z\",\"ns\":\"StateQueryServer.Receive.Done\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgDone\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"}},\"sev\":\"Info\",\"thread\":\"96\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.03524875Z\",\"ns\":\"Net.Mux.Local.CleanExit\",\"data\":{\"bearer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@2\\\"\"},\"event\":{\"kind\":\"Mux.TraceCleanExit\",\"miniProtocolDir\":\"ResponderDir\",\"miniProtocolNum\":\"MiniProtocolNum 7\",\"msg\":\"Miniprotocol terminated cleanly\"},\"kind\":\"Mux.Trace\"},\"sev\":\"Notice\",\"thread\":\"93\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM":"2315","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023085731","_GID":"10016","__MONOTONIC_TIMESTAMP":"29808858","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90b;b=082ebd52b7694299b9566558b64d809c;m=1c6d8da;t=641e8937f74a3;x=4c4531e35767854c"} +{"_TRANSPORT":"stdout","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023150568","_PID":"759","__MONOTONIC_TIMESTAMP":"29873698","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90c;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=e4a1f42dad9426a6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2316","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:42.992959018Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90d;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=63eb4a2c25355dc2","__MONOTONIC_TIMESTAMP":"29873698","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2317","_TRANSPORT":"stdout","PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023150568","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.036271506Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2318","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.042697462Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"6a1714525659a774a054f82ee4ab0280246ba955d92ea664b63f11fedc9e09ab\",\"kind\":\"BlockPoint\",\"slot\":558}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"29873698","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__REALTIME_TIMESTAMP":"1761317023150568","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90e;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=f52c433aef2f01f8","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"PRIORITY":"6","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=90f;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=8bf215a178449b49","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2319","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023150568","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29873698","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.04274244Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":558}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node"} +{"_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.09152769Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"29873698","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=910;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=855ea4f6c5bdd993","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2320","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023150568"} +{"PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.091577976Z\",\"ns\":\"Net.InboundGovernor.Local.WaitIdleRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"WaitIdleRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundSt\"}}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=911;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=4087d6b0c65230d","__REALTIME_TIMESTAMP":"1761317023150568","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"29873698","__SEQNUM":"2321","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=912;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=168176fefda495c5","_GID":"10016","_UID":"10016","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.091619602Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"29873698","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"2322","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317023150568","PRIORITY":"6"} +{"PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.09165983Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_GID":"10016","__MONOTONIC_TIMESTAMP":"29873698","__REALTIME_TIMESTAMP":"1761317023150568","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=913;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=9ab56b1ab8d3480a","_PID":"759","__SEQNUM":"2323","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"29873698","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2324","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=914;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=1a46e453ac112765","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.091746433Z\",\"ns\":\"Net.InboundGovernor.Local.ResponderRestarted\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"ResponderStarted\",\"miniProtocolNum\":{\"kind\":\"MiniProtocolNum\",\"num\":7}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317023150568"} +{"__MONOTONIC_TIMESTAMP":"29873698","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.091780795Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=915;b=082ebd52b7694299b9566558b64d809c;m=1c7d622;t=641e8938071e8;x=d67efd4918068b9a","_COMM":"cardano-node","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2325","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023150568"} +{"SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"29935378","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=916;b=082ebd52b7694299b9566558b64d809c;m=1c8c712;t=641e8938162da;x=d216e67477be0d48","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM":"2326","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.150179558Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"BlockPoint\",\"slot\":602},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023212250","_COMM":"cardano-node","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.198490167Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"events\":[{\"epochNo\":\"EpochNo 2\",\"kind\":\"ShelleyUpdatedProtocolUpdates\",\"updates\":\"SNothing\"}],\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":35,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":602,\"tieBreakVRF\":\"713fe8793dfe40bb9ba9315f6f1aca910bd7c9fdf8e74adc2b02494d9c37b6bc387ff810fc425fa6c26142dd07b1fc09c5ff17814bcda5532a1835f66fe260cc\"},\"newtip\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602\",\"oldTipSelectView\":{\"chainLength\":34,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":588,\"tieBreakVRF\":\"2c378d8710efaab90d72652d042886ef8d1d4b1365d016c30267cebd038f2a77c1b6bcb7fd121ad12840541641b1f4c3ca21985b8847eebceb927c82be65018d\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2327","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__MONOTONIC_TIMESTAMP":"29942566","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023219434","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=917;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=82bdc3dd661a5c9c","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__SEQNUM":"2328","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"29942566","SYSLOG_FACILITY":"3","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=918;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=53d20f9b08d65e98","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.198691031Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b@602\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023219434"} +{"SYSLOG_FACILITY":"3","PRIORITY":"6","_GID":"10016","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.198777634Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=919;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=708f21cc080528cd","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023219434","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"29942566","_RUNTIME_SCOPE":"system","__SEQNUM":"2329","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023219434","_RUNTIME_SCOPE":"system","__SEQNUM":"2330","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.198804174Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"Point\",\"slot\":707},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"29942566","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91a;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=e08d5c173b28874","_COMM":"cardano-node"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.218365878Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":580}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"29942566","__REALTIME_TIMESTAMP":"1761317023219434","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91b;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=eba03b267d038eb9","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2331","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_GID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.218499694Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":780},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023219434","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"29942566","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91c;b=082ebd52b7694299b9566558b64d809c;m=1c8e326;t=641e893817eea;x=7d38fe74c81d4d4b","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_PID":"759","PRIORITY":"6","__SEQNUM":"2332","_UID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023262279","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__SEQNUM":"2333","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"29985409","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.241418249Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"ef8f495f901bc62d7b48488bb3a13e9e96ba35e75efb78c2a0fcb0d7e8ee17cb\",\"kind\":\"BlockPoint\",\"slot\":580},\"head\":{\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"BlockPoint\",\"slot\":602}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91d;b=082ebd52b7694299b9566558b64d809c;m=1c98a81;t=641e893822647;x=99645ec1962630ab","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service"} +{"SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.241479989Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"Point\",\"slot\":707},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2334","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317023262279","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91e;b=082ebd52b7694299b9566558b64d809c;m=1c98a81;t=641e893822647;x=f9e4b8c48931aebd","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"29985409","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__SEQNUM":"2335","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=91f;b=082ebd52b7694299b9566558b64d809c;m=1c98a81;t=641e893822647;x=edc06a524ca3bf81","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023262279","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"29985409","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_GID":"10016","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.241538097Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_PID":"759"} +{"_TRANSPORT":"stdout","_UID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.24155849Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=920;b=082ebd52b7694299b9566558b64d809c;m=1c9e304;t=641e893827ecb;x=eaa4bc4bd0269478","_RUNTIME_SCOPE":"system","__SEQNUM":"2336","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023284939","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30008068","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023290427","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=921;b=082ebd52b7694299b9566558b64d809c;m=1c9f875;t=641e89382943b;x=dd6c3578d643d8fd","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_PID":"759","__MONOTONIC_TIMESTAMP":"30013557","__SEQNUM":"2337","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.284767893Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.289739195Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":41,\"headerHash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=922;b=082ebd52b7694299b9566558b64d809c;m=1ca12a6;t=641e89382ae6c;x=18ff8a1c9e3bbbe2","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023297132","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016","__SEQNUM":"2338","__MONOTONIC_TIMESTAMP":"30020262","_GID":"10016"} +{"_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.289791436Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"30026424","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=923;b=082ebd52b7694299b9566558b64d809c;m=1ca2ab8;t=641e89382c67d;x=cbc74dbeab4269b0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023303293","_HOSTNAME":"leios-node","PRIORITY":"6","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM":"2339","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.289833341Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023303293","__SEQNUM":"2340","__MONOTONIC_TIMESTAMP":"30026424","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=924;b=082ebd52b7694299b9566558b64d809c;m=1ca2ab8;t=641e89382c67d;x=832d32b3194e986f"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023315492","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=925;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=1d9008ad9a51c2d","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2341","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"30038622","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.290217189Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_PID":"759","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.295796389Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"blockNo\":43,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":795},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=926;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=eaef4369fed925e8","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"30038622","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023315492","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__SEQNUM":"2342","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_PID":"759","_CAP_EFFECTIVE":"0","_UID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.296060669Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":795},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30038622","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM":"2343","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=927;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=b3a423c20c633f54","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023315492"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.296780034Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"BlockPoint\",\"slot\":707},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=928;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=27546478201a4b61","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023315492","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__SEQNUM":"2344","_UID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30038622","_CAP_EFFECTIVE":"0"} +{"_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30038622","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2345","__REALTIME_TIMESTAMP":"1761317023315492","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=929;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=69ee88b292caef0e","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.309073496Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"PRIORITY":"6","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92a;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=1203cb29da5dde84","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317023315492","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"30038622","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.309130766Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2346","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016"} +{"SYSLOG_FACILITY":"3","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2347","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92b;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=89912e010365029e","_UID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023315492","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"30038622","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.309273521Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720@707\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0"} +{"_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023315492","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.30936208Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_GID":"10016","__MONOTONIC_TIMESTAMP":"30038622","_RUNTIME_SCOPE":"system","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2348","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92c;b=082ebd52b7694299b9566558b64d809c;m=1ca5a5e;t=641e89382f624;x=fe9750234658eea9"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"30085566","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92d;b=082ebd52b7694299b9566558b64d809c;m=1cb11be;t=641e89383ad84;x=c67a13902f44f644","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:42.44641218 UTC to 2025-10-24 14:43:43.328295212 UTC","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_GID":"10016","PRIORITY":"6","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023362436","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2349","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92e;b=082ebd52b7694299b9566558b64d809c;m=1cb2bb1;t=641e89383c776;x=e01546438eda46b3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30092209","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM":"2350","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.309387502Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"Point\",\"slot\":710},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023369078","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=92f;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=d665bcb2086dcee1","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30099146","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.328295212Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"a1bd89bc62f2796c8f1319e8d613437c7cd456cfde21613c699720da38370ea9\",\"kind\":\"BlockPoint\",\"slot\":581},\"head\":{\"headerHash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"BlockPoint\",\"slot\":707}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023376019","PRIORITY":"6","_UID":"10016","__SEQNUM":"2351","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_SLICE":"system.slice"} +{"_COMM":"cardano-node","__SEQNUM":"2352","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023376019","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__MONOTONIC_TIMESTAMP":"30099146","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=930;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=fb4e659bb909d040","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.328354997Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"Point\",\"slot\":710},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_GID":"10016"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.328744432Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=931;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=a96a82e79a558ff0","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__REALTIME_TIMESTAMP":"1761317023376019","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2353","_GID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"30099146"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023376019","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.328793879Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=932;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=bd45d8aacd34c3ed","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30099146","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_PID":"759","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2354","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_GID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023376019","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30099146","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.350586593Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":795},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=933;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=c314183112f9f4b8","__SEQNUM":"2355","_RUNTIME_SCOPE":"system"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2356","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30099146","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=934;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=5db981e032461a6f","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.367569198Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023376019","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__SEQNUM":"2357","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023376019","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.367660551Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":42,\"headerHash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=935;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=95e876872fe97d1b","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"30099146","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"30099146","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=936;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=267eade0731e61a6","__REALTIME_TIMESTAMP":"1761317023376019","_TRANSPORT":"stdout","_PID":"759","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_GID":"10016","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.367697148Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM":"2358","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_PID":"759","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.367725084Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30099146","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317023376019","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=937;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=b0fc7f6be0b898c9","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM":"2359","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=938;b=082ebd52b7694299b9566558b64d809c;m=1cb46ca;t=641e89383e293;x=b64afe43e627f4c4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_PID":"759","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30099146","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.367767268Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"blockNo\":44,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":809},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","__SEQNUM":"2360","__REALTIME_TIMESTAMP":"1761317023376019","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023438772","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.384615499Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"BlockPoint\",\"slot\":710},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30161899","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=939;b=082ebd52b7694299b9566558b64d809c;m=1cc3beb;t=641e89384d7b4;x=5d3c8fe75d72e848","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2361","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759"} +{"_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"30161899","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.384781163Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7@710\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317023438772","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93a;b=082ebd52b7694299b9566558b64d809c;m=1cc3beb;t=641e89384d7b4;x=aa2e97ce0463e818","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2362","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30161899","_SYSTEMD_SLICE":"system.slice","_PID":"759","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.384859105Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93b;b=082ebd52b7694299b9566558b64d809c;m=1cc3beb;t=641e89384d7b4;x=2d2478607e5ca0a6","_TRANSPORT":"stdout","__SEQNUM":"2363","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023438772","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__MONOTONIC_TIMESTAMP":"30161899","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317023438772","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.402771997Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":581}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM":"2364","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93c;b=082ebd52b7694299b9566558b64d809c;m=1cc3beb;t=641e89384d7b4;x=74c0cca35e5d6d3d"} +{"_COMM":"cardano-node","PRIORITY":"6","_RUNTIME_SCOPE":"system","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30185071","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93d;b=082ebd52b7694299b9566558b64d809c;m=1cc966f;t=641e893853236;x=6838bc9d4485878c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.432727759Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_UID":"10016","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023461942","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_PID":"759","__SEQNUM":"2365"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317023468056","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93e;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=39122fb15fcf1834","__SEQNUM":"2366","__MONOTONIC_TIMESTAMP":"30191183","_CAP_EFFECTIVE":"0","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_TRANSPORT":"stdout","_COMM":"cardano-node","_PID":"759","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.439002858Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"30191183","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.439130528Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":43,\"headerHash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_RUNTIME_SCOPE":"system","__SEQNUM":"2367","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023468056","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=93f;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=edc59b356318f41e","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_HOSTNAME":"leios-node","__SEQNUM":"2368","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30191183","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023468056","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=940;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=30fe45d66e6e98e5","_GID":"10016","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.439167684Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016"} +{"__SEQNUM":"2369","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.439194503Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30191183","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023468056","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=941;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=354d0a2356aa37cf","_PID":"759","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_TRANSPORT":"stdout"} +{"_RUNTIME_SCOPE":"system","__SEQNUM":"2370","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=942;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=cb083970cceff201","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_GID":"10016","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30191183","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.439236408Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"blockNo\":45,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":810},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023468056","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_PID":"759","__REALTIME_TIMESTAMP":"1761317023468056","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=943;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=56df3536240b8cc3","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.46003095Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"Point\",\"slot\":728},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2371","__MONOTONIC_TIMESTAMP":"30191183","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=944;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=81959a2326ebcfca","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.460185718Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"Point\",\"slot\":728},\"blockNo\":\"38\",\"kind\":\"AddedBlockToVolatileDB\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023468056","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2372","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__MONOTONIC_TIMESTAMP":"30191183","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node"} +{"_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=945;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=3cb1f097dd4e2f71","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023468056","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.461185007Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_PID":"759","__SEQNUM":"2373","__MONOTONIC_TIMESTAMP":"30191183"} +{"_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_GID":"10016","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=946;b=082ebd52b7694299b9566558b64d809c;m=1ccae4f;t=641e893854a18;x=3698d0c5b9f3e6ee","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.461245629Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30191183","_COMM":"cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023468056","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2374"} +{"SYSLOG_FACILITY":"3","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_GID":"10016","__MONOTONIC_TIMESTAMP":"30245155","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.466592119Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":588}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=947;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=ff2ff684eeba3175","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2375","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023522026"} +{"_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30245155","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM":"2376","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023522026","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=948;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=fa72eeba7fc62da6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.485181353Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"d83ade26db7c6dc83d21167b639efb090416773eed69dc991372b4c7cbfbef88\",\"kind\":\"BlockPoint\",\"slot\":588},\"head\":{\"headerHash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"BlockPoint\",\"slot\":710}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_PID":"759"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30245155","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317023522026","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_COMM":"cardano-node","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=949;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=745ffc9be5c53afe","_UID":"10016","__SEQNUM":"2377","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.485255944Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"Point\",\"slot\":728},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_PID":"759","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.48533668Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94a;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=47cef56bf04ec76a","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30245155","_SYSTEMD_SLICE":"system.slice","_GID":"10016","PRIORITY":"6","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023522026","_COMM":"cardano-node","__SEQNUM":"2378","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023522026","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30245155","__SEQNUM":"2379","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.485370483Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94b;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=5fb5434a168487dc","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6"} +{"_GID":"10016","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.503375006Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"2380","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94c;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=26fccf48a954d4ec","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30245155","__REALTIME_TIMESTAMP":"1761317023522026","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_RUNTIME_SCOPE":"system"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","PRIORITY":"6","_GID":"10016","__SEQNUM":"2381","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94d;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=49d66ba31c678893","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30245155","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023522026","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.503485914Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":44,\"headerHash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0"} +{"SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30245155","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.503521673Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","PRIORITY":"6","_COMM":"cardano-node","_UID":"10016","__SEQNUM":"2382","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94e;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=d0815c96b8b44232","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317023522026"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=94f;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=69da2146f545376c","__SEQNUM":"2383","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30245155","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.503547374Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317023522026","_CAP_EFFECTIVE":"0","_GID":"10016","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023522026","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=950;b=082ebd52b7694299b9566558b64d809c;m=1cd8123;t=641e893861cea;x=faaba8869a627164","__MONOTONIC_TIMESTAMP":"30245155","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.503587324Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"blockNo\":46,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":829},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2384","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.540239468Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"30308100","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=951;b=082ebd52b7694299b9566558b64d809c;m=1ce7704;t=641e8938712cb;x=c95a01e539bd8504","__SEQNUM":"2385","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023584971","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023590323","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","__SEQNUM":"2386","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=952;b=082ebd52b7694299b9566558b64d809c;m=1ce8bee;t=641e8938727b3;x=99e21f83874008f","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.540707684Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_GID":"10016","__MONOTONIC_TIMESTAMP":"30313454","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__SEQNUM":"2387","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=953;b=082ebd52b7694299b9566558b64d809c;m=1cea14c;t=641e893873d0f;x=b7118b73513ba775","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.550667609Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","__REALTIME_TIMESTAMP":"1761317023595791","PRIORITY":"6","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30318924","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3"} +{"_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30327116","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=954;b=082ebd52b7694299b9566558b64d809c;m=1cec14c;t=641e893875d12;x=6186cc3dd53cced9","SYSLOG_FACILITY":"3","__SEQNUM":"2388","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.576651358Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"BlockPoint\",\"slot\":728},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317023603986","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node"} +{"_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2389","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=955;b=082ebd52b7694299b9566558b64d809c;m=1ced81c;t=641e8938773e0;x=22ac615c8d04cf45","_TRANSPORT":"stdout","_PID":"759","__REALTIME_TIMESTAMP":"1761317023609824","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"30332956","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.582768616Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node"} +{"_UID":"10016","__MONOTONIC_TIMESTAMP":"30340802","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.582992388Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":45,\"headerHash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=956;b=082ebd52b7694299b9566558b64d809c;m=1cef6c2;t=641e893879283;x=a32fa5f5c48b628d","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_PID":"759","PRIORITY":"6","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2390","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317023617667","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=957;b=082ebd52b7694299b9566558b64d809c;m=1cf1cb0;t=641e89387b875;x=f46154c97ce1bed1","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"30350512","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","PRIORITY":"6","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317023627381","SYSLOG_FACILITY":"3","__SEQNUM":"2391","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.583028426Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node"} +{"_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30359654","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.583053848Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","PRIORITY":"6","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=958;b=082ebd52b7694299b9566558b64d809c;m=1cf4066;t=641e89387dc28;x=b674f94ca08bff3a","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2392","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023636520","_GID":"10016"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=959;b=082ebd52b7694299b9566558b64d809c;m=1cf5536;t=641e89387f0fb;x=180baa6eb5297260","_HOSTNAME":"leios-node","_GID":"10016","_UID":"10016","_COMM":"cardano-node","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2393","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.583096032Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"blockNo\":47,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":863},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"30364982","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317023641851","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_UID":"10016","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2394","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95a;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=97d6296832b1c030","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"30374147","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.58371762Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317023651014"} +{"_GID":"10016","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95b;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=11a3be0d46b1ca3e","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30374147","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.583758407Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2395","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317023651014"} +{"_RUNTIME_SCOPE":"system","_UID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30374147","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.584024921Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"Point\",\"slot\":780},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023651014","__SEQNUM":"2396","_PID":"759","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95c;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=5c681c82b1a838e2"} +{"_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023651014","__SEQNUM":"2397","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30374147","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.584115994Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"delay\":1363629.550797793,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95d;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=177724e5065ede53","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","PRIORITY":"6","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95e;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=4c7960ac91672157","PRIORITY":"6","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30374147","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317023651014","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2398","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.584178293Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016"} +{"__SEQNUM":"2399","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"30374147","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=95f;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=15838296e64e8ab2","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023651014","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.584240312Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.584581696Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023651014","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30374147","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=960;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=a96d913a585c8639","__SEQNUM":"2400","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_TRANSPORT":"stdout","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.589417506Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317023651014","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM":"2401","__MONOTONIC_TIMESTAMP":"30374147","_UID":"10016","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=961;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=27acf88332cf23a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM":"2402","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30374147","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_COMM":"cardano-node","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023651014","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=962;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=ff14afb6a9827541","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600101266Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf@728\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice"} +{"SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=963;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=6ca6c10cefa70d1","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600208263Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"30374147","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023651014","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2403","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30374147","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600233406Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"Point\",\"slot\":740},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=964;b=082ebd52b7694299b9566558b64d809c;m=1cf7903;t=641e8938814c6;x=5b241a6f440f30ae","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317023651014","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_UID":"10016","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM":"2404","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023707032","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=965;b=082ebd52b7694299b9566558b64d809c;m=1d053d1;t=641e89388ef98;x=f5d4dcedd522bc1a","__SEQNUM":"2405","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600498803Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"BlockPoint\",\"slot\":602},\"head\":{\"headerHash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"BlockPoint\",\"slot\":728}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30430161","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_PID":"759","_GID":"10016"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=966;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=3c0a2a841c39dd3f","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30439067","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__SEQNUM":"2406","PRIORITY":"6","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023715938","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600530091Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"Point\",\"slot\":740},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","_PID":"759"} +{"__MONOTONIC_TIMESTAMP":"30439067","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=967;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=3b31ae6f371b965c","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023715938","PRIORITY":"6","_PID":"759","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__SEQNUM":"2407","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.60057926Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=968;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=cc5147a75697be3d","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600598536Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317023715938","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"30439067","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2408","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_GID":"10016"} +{"_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023715938","__MONOTONIC_TIMESTAMP":"30439067","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=969;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=e096c2dbc9e8d151","PRIORITY":"6","_CAP_EFFECTIVE":"0","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2409","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.600626752Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}"} +{"_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.60065413Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96a;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=7faf624b18ba2208","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023715938","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__SEQNUM":"2410","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30439067","_CAP_EFFECTIVE":"0","_GID":"10016","_PID":"759","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.601736111Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96b;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=472501ca3e9558d3","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2411","SYSLOG_FACILITY":"3","PRIORITY":"6","_CAP_EFFECTIVE":"0","_UID":"10016","__REALTIME_TIMESTAMP":"1761317023715938","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_PID":"759","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30439067","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023715938","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96c;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=267ffba0d00b5283","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.601816288Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":46,\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","PRIORITY":"6","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"30439067","__SEQNUM":"2412","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_TRANSPORT":"stdout"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.601848974Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_UID":"10016","__SEQNUM":"2413","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317023715938","__MONOTONIC_TIMESTAMP":"30439067","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96d;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=ebf59a57e701bfdf","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.601943958Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30439067","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM":"2414","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96e;b=082ebd52b7694299b9566558b64d809c;m=1d0769b;t=641e893891262;x=28ba8a9aedf152b0","_GID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317023715938","_HOSTNAME":"leios-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=96f;b=082ebd52b7694299b9566558b64d809c;m=1d12c44;t=641e89389c80d;x=e5fb96693221edc8","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2415","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.601987819Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"blockNo\":48,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":887},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","PRIORITY":"6","_PID":"759","__REALTIME_TIMESTAMP":"1761317023762445","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"30485572","_UID":"10016","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice"} +{"__MONOTONIC_TIMESTAMP":"30485572","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.616241306Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2416","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=970;b=082ebd52b7694299b9566558b64d809c;m=1d12c44;t=641e89389c80d;x=be4ecd4550db0e1f","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317023762445","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30485572","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.616369535Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":47,\"headerHash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM":"2417","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=971;b=082ebd52b7694299b9566558b64d809c;m=1d12c44;t=641e89389c80d;x=be4e6b4163fff499","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023762445","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__MONOTONIC_TIMESTAMP":"30485572","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.616414513Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__SEQNUM":"2418","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_PID":"759","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=972;b=082ebd52b7694299b9566558b64d809c;m=1d12c44;t=641e89389c80d;x=48b919d150b07a55","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023762445","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0"} +{"__REALTIME_TIMESTAMP":"1761317023762445","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=973;b=082ebd52b7694299b9566558b64d809c;m=1d12c44;t=641e89389c80d;x=da88e6c362aed077","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30485572","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_UID":"10016","_PID":"759","__SEQNUM":"2419","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.616451389Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.61650782Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"blockNo\":49,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":907},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=974;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=ed22831eaf6ca137","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023798960","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__SEQNUM":"2420","__MONOTONIC_TIMESTAMP":"30522091","SYSLOG_FACILITY":"3"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.617029954Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"BlockPoint\",\"slot\":740},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2421","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30522091","__REALTIME_TIMESTAMP":"1761317023798960","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=975;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=c93abe607fd973c1","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_HOSTNAME":"leios-node","_UID":"10016"} +{"_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30522091","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=976;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=6a8cef7dceff7fd9","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2422","__REALTIME_TIMESTAMP":"1761317023798960","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.617169078Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e@740\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023798960","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=977;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=6fefb0159c8a4fce","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.61724283Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2423","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30522091"} +{"_UID":"10016","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2424","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.617266297Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"Point\",\"slot\":746},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"30522091","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=978;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=f296c163cb467dde","__REALTIME_TIMESTAMP":"1761317023798960","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_GID":"10016"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=979;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=4c25c9a23d551dd","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317023798960","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.626323034Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30522091","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM":"2425","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023798960","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_PID":"759","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2426","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97a;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=c33596e644da0f80","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30522091","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.626602679Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"a832dcac2e51c974c514fac16753de3e6d23f5a242ebe34083dce2ecb9a3404b\",\"kind\":\"BlockPoint\",\"slot\":602}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.626642349Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":602}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30522091","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97b;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=5c5c327a19d9d415","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023798960","__SEQNUM":"2427","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node"} +{"_COMM":"cardano-node","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317023798960","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97c;b=082ebd52b7694299b9566558b64d809c;m=1d1baeb;t=641e8938a56b0;x=2c22c91ef96ee081","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.627099111Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"435973cbed0926697a804e2c77b53e6fbe0cbaf1ff0229c8c4c935b7a7169720\",\"kind\":\"BlockPoint\",\"slot\":707},\"head\":{\"headerHash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"BlockPoint\",\"slot\":740}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2428","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30522091","_SYSTEMD_UNIT":"cardano-node.service"} +{"_COMM":"cardano-node","__SEQNUM":"2429","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"30579292","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.627132914Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"Point\",\"slot\":746},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023856165","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_PID":"759","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97d;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=8437eac1c4dd77c2"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_GID":"10016","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.6271832Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM":"2430","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30579292","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97e;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=2c2b9107df8a94ac","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317023856165","_CAP_EFFECTIVE":"0"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.627202755Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_HOSTNAME":"leios-node","__SEQNUM":"2431","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=97f;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=75d999975e7d382d","__MONOTONIC_TIMESTAMP":"30579292","__REALTIME_TIMESTAMP":"1761317023856165","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node"} +{"SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_GID":"10016","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.633300737Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2432","__MONOTONIC_TIMESTAMP":"30579292","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=980;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=a3903c94814532f1","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023856165","_SYSTEMD_UNIT":"cardano-node.service"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__MONOTONIC_TIMESTAMP":"30579292","__SEQNUM":"2433","__REALTIME_TIMESTAMP":"1761317023856165","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.633347391Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"SendFetchRequest\",\"length\":2,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=981;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=86635bd28961ada9"} +{"__MONOTONIC_TIMESTAMP":"30579292","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.634463175Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"BlockPoint\",\"slot\":746},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317023856165","PRIORITY":"6","__SEQNUM":"2434","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=982;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=98b04b0038c8317b"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=983;b=082ebd52b7694299b9566558b64d809c;m=1d29a5c;t=641e8938b3625;x=803820bde214d1a7","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.634609842Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778@746\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","__REALTIME_TIMESTAMP":"1761317023856165","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30579292","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__SEQNUM":"2435","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__SEQNUM":"2436","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=984;b=082ebd52b7694299b9566558b64d809c;m=1d34dfb;t=641e8938be9c0;x=b76fe667534d34c9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"30625275","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_GID":"10016","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023902144","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.634677448Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=985;b=082ebd52b7694299b9566558b64d809c;m=1d34dfb;t=641e8938be9c0;x=b8a91739c4282f6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30625275","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2437","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.634700635Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"Point\",\"slot\":756},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023902144","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_HOSTNAME":"leios-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023915818","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__SEQNUM":"2438","_COMM":"cardano-node","_GID":"10016","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30638946","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=986;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=a5814d471b14621b","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.63537614Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.635453524Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":48,\"headerHash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=987;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=d5ba0a234756ef1f","__SEQNUM":"2439","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023915818","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30638946"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30638946","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023915818","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.635487048Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM":"2440","_PID":"759","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=988;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=19b71800f01da6d6","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.635512471Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_COMM":"cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=989;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=3e23a93c9f15d331","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30638946","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023915818","_UID":"10016","__SEQNUM":"2441","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2442","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023915818","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98a;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=32cc716da85ffb94","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30638946","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.63623854Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30638946","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2443","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.647566796Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0dccbe69ff9175fdadac864443fc4ffd850d31537f4a8f82171d0e3e34e45ea7\",\"kind\":\"BlockPoint\",\"slot\":710},\"head\":{\"headerHash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"BlockPoint\",\"slot\":746}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98b;b=082ebd52b7694299b9566558b64d809c;m=1d38362;t=641e8938c1f2a;x=19b19b6c01db027d","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023915818","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98c;b=082ebd52b7694299b9566558b64d809c;m=1d42533;t=641e8938cc0f8;x=75fc5cfbef909712","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30680371","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2444","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317023957240","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.647607304Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"Point\",\"slot\":756},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.647666529Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98d;b=082ebd52b7694299b9566558b64d809c;m=1d42533;t=641e8938cc0f8;x=d54b6c12a3e96cbd","_UID":"10016","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2445","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317023957240","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__MONOTONIC_TIMESTAMP":"30680371","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice"} +{"_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023957240","_TRANSPORT":"stdout","PRIORITY":"6","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98e;b=082ebd52b7694299b9566558b64d809c;m=1d42533;t=641e8938cc0f8;x=993282d995dcae33","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.647685526Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"30680371","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__SEQNUM":"2446","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30701313","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.64810625Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":707}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2447","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317023978182","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=98f;b=082ebd52b7694299b9566558b64d809c;m=1d47701;t=641e8938d12c6;x=59eb786c0fab231a"} +{"_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023983067","__MONOTONIC_TIMESTAMP":"30706196","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=990;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=354d5079fbfb613b","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__SEQNUM":"2448","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","PRIORITY":"6","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.648694034Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":710}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:43.64931618Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_GID":"10016","_PID":"759","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30706196","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=991;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=212cb0645c2cc48f","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_UID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2449","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317023983067","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service"} +{"_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM":"2450","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023983067","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.649350542Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"30706196","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=992;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=18878fc3a3534d2b"} +{"__REALTIME_TIMESTAMP":"1761317023983067","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=993;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=37696ec516ec37e1","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__SEQNUM":"2451","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.649410326Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30706196","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2452","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317023983067","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.649845018Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=994;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=e26304aa5bc5754f","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_PID":"759","__MONOTONIC_TIMESTAMP":"30706196"} +{"_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=995;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=aeb811a3853d2170","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023983067","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30706196","PRIORITY":"6","_TRANSPORT":"stdout","_COMM":"cardano-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.67315664Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM":"2453","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2454","__REALTIME_TIMESTAMP":"1761317023983067","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"30706196","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_GID":"10016","_HOSTNAME":"leios-node","PRIORITY":"6","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=996;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=b06d9d6e8a39a957","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.673590494Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}"} +{"__REALTIME_TIMESTAMP":"1761317023983067","__SEQNUM":"2455","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"30706196","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=997;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=4ffde1d797523a4e","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_UID":"10016","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.70626867Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"BlockPoint\",\"slot\":756},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice"} +{"_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317023983067","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.706430143Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3@756\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_GID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=998;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=43ba5e0f1c9868fa","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__SEQNUM":"2456","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"30706196","_RUNTIME_SCOPE":"system"} +{"_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.706503616Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023983067","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_GID":"10016","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=999;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=d474928ffa1bcbaa","__MONOTONIC_TIMESTAMP":"30706196","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2457","SYSLOG_FACILITY":"3"} +{"_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99a;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=4348557c3e51d582","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.70652848Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"Point\",\"slot\":780},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__SEQNUM":"2458","_GID":"10016","PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023983067","__MONOTONIC_TIMESTAMP":"30706196","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99b;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=7d15def19c98ef29","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30706196","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.741273119Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"e4e8468096090e84bb353b085f81a1f90af89aaa9562b3bdeadb31945938edcf\",\"kind\":\"BlockPoint\",\"slot\":728},\"head\":{\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"BlockPoint\",\"slot\":756}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM":"2459","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023983067"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99c;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=ea62c0242f72817e","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.741313347Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"Point\",\"slot\":780},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__SEQNUM":"2460","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_COMM":"cardano-node","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317023983067","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30706196"} +{"_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99d;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=856b3bebfc2a71fc","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317023983067","_PID":"759","__MONOTONIC_TIMESTAMP":"30706196","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.741367544Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2461","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30706196","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99e;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=51b4ab6c8e91f3ef","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.741387659Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2462","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","__REALTIME_TIMESTAMP":"1761317023983067"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2463","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.775540603Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_PID":"759","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317023983067","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=99f;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=76ecf3b2b79f53c1","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"30706196"} +{"_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a0;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=600e034dae0291ff","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317023983067","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.797209837Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":284967296,\"CentiBlkIO\":0,\"CentiCpu\":119,\"CentiGC\":2,\"CentiMut\":109,\"FsRd\":50929664,\"FsWr\":344064,\"GcsMajor\":2,\"GcsMinor\":7,\"Heap\":49283072,\"Live\":4599904,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","__SEQNUM":"2464","__MONOTONIC_TIMESTAMP":"30706196","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__REALTIME_TIMESTAMP":"1761317023983067","PRIORITY":"6","_COMM":"cardano-node","__SEQNUM":"2465","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a1;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=9244c615b7990d16","_UID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.813812226Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":728}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"30706196","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317023983067","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"30706196","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a2;b=082ebd52b7694299b9566558b64d809c;m=1d48a14;t=641e8938d25db;x=e4ba8a291eb547f2","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.82585845Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM":"2466","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","PRIORITY":"6"} +{"_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024102394","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a3;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=82d3d29cfc95c19f","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"30825535","__SEQNUM":"2467","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:43.328354997 UTC to 2025-10-24 14:43:43.977369047 UTC","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_PID":"759"} +{"_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a4;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=c6afa48e7a431ebb","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024102394","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2468","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30825535","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.832425765Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"30825535","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.843503989Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"blockNo\":50,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":984},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a5;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=2c1157ded81aad8a","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2469","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317024102394","PRIORITY":"6"} +{"_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.856467648Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"BlockPoint\",\"slot\":780},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a6;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=53fae4013ed73d92","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317024102394","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2470","__MONOTONIC_TIMESTAMP":"30825535","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_COMM":"cardano-node"} +{"_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_COMM":"cardano-node","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2471","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"30825535","__REALTIME_TIMESTAMP":"1761317024102394","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.856621019Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":42,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":780,\"tieBreakVRF\":\"2d0124c8d3305a9b30eddd2cb1d934c0c887708c5a35cdd5ecdbfba583356b0990ae426ad66962591f5076a815c3c94be5b613d5212c4da797653fcb6fe5537a\"},\"newtip\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"oldTipSelectView\":{\"chainLength\":41,\"issueNo\":0,\"issuerHash\":\"4c26da5ee3f61915d2df4167a53394b1f033623042a8d26ab7af5ef7\",\"kind\":\"PraosChainSelectView\",\"slotNo\":756,\"tieBreakVRF\":\"9021dc8dbff79e7f4dfa70ff22178a1c0cdefa937b7c461e3f2d3b028812c3bff1ed9bd46181e1e7a402226e15cad240fa9a5cab33528576df4d6be8cdb4afc5\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a7;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=1fd4c150b6ef6a7","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a8;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=534e975c41b6dafb","_GID":"10016","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.856739749Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98@780\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317024102394","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2472","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30825535","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024102394","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9a9;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=3cbda428244d1a97","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","PRIORITY":"6","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"30825535","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2473","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.85682328Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024102394","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9aa;b=082ebd52b7694299b9566558b64d809c;m=1d65c3f;t=641e8938ef7fa;x=f2cbdd23cdb8a215","SYSLOG_FACILITY":"3","_PID":"759","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30825535","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.856847026Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"Point\",\"slot\":795},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_COMM":"cardano-node","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__SEQNUM":"2474"} +{"_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_COMM":"cardano-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.901769215Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":984},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"30882691","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2475","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024159563","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ab;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=d8e490c1d3bcfda0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024159563","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ac;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=71ffd529091ba733","_GID":"10016","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.93120061Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30882691","__SEQNUM":"2476","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_HOSTNAME":"leios-node"} +{"__MONOTONIC_TIMESTAMP":"30882691","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__REALTIME_TIMESTAMP":"1761317024159563","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ad;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=1702d6c1988b907","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_UID":"10016","PRIORITY":"6","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.97658012Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":740}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2477","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ae;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=28dd904c2cda90e6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"30882691","__REALTIME_TIMESTAMP":"1761317024159563","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2478","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.977106444Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"Point\",\"slot\":795},\"blockNo\":\"43\",\"kind\":\"AddedBlockToVolatileDB\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2479","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9af;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=8dcf11e0f6d430b5","__REALTIME_TIMESTAMP":"1761317024159563","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.977304514Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"120f49d7e36dc48942668ea306896c50afc446fe3ddd4baa16641786c3a1246e\",\"kind\":\"BlockPoint\",\"slot\":740},\"head\":{\"headerHash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"BlockPoint\",\"slot\":780}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30882691"} +{"_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317024159563","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__SEQNUM":"2480","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.977369047Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"Point\",\"slot\":795},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"30882691","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b0;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=2b061e442cfcdefd","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.978033377Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__SEQNUM":"2481","__MONOTONIC_TIMESTAMP":"30882691","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b1;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=61b123f2840fc217","__REALTIME_TIMESTAMP":"1761317024159563","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3"} +{"SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317024159563","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b2;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=a3389fc9ddc2a6c0","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:43.999438612Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_UID":"10016","__SEQNUM":"2482","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30882691","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.018842195Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"BlockPoint\",\"slot\":795},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30882691","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317024159563","PRIORITY":"6","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b3;b=082ebd52b7694299b9566558b64d809c;m=1d73b83;t=641e8938fd74b;x=354475f49721172f","__SEQNUM":"2483","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.047727151Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionCleanup\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"ConnectionCleanup\"},\"sev\":\"Debug\",\"thread\":\"93\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_GID":"10016","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024220102","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b4;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=1a73cf17bbbfd7b1","__MONOTONIC_TIMESTAMP":"30943229","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2484","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2485","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.047796993Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":0,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"93\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b5;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=e9baf403f06618e2","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_UID":"10016","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"30943229","__REALTIME_TIMESTAMP":"1761317024220102","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016"} +{"_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"30943229","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.056438873Z\",\"ns\":\"Net.InboundGovernor.Local.MuxCleanExit\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@2\"},\"kind\":\"MuxCleanExit\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b6;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=846123430f44aa66","__SEQNUM":"2486","__REALTIME_TIMESTAMP":"1761317024220102"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2487","_TRANSPORT":"stdout","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b7;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=b7a536e5ca606466","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317024220102","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"30943229","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.056481895Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}"} +{"_PID":"759","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b8;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=9f62db7820a0a738","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024220102","_COMM":"cardano-node","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.056513184Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"30943229","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"2488","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.063455687Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a@795\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9b9;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=69ddd14817e92b2f","__REALTIME_TIMESTAMP":"1761317024220102","__MONOTONIC_TIMESTAMP":"30943229","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"2489","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ba;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=3d12217a3cec1999","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.063577211Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2490","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024220102","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"30943229","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_UID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_COMM":"cardano-node","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"30943229","__SEQNUM":"2491","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.063611014Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"Point\",\"slot\":809},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024220102","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9bb;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=f660a569dd2af4c9","PRIORITY":"6","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__REALTIME_TIMESTAMP":"1761317024220102","_PID":"759","__MONOTONIC_TIMESTAMP":"30943229","_HOSTNAME":"leios-node","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.105190321Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0e7f6e60bc935347a817bd37b4943746dbe5a0905a0f87f8f76f1a586883c778\",\"kind\":\"BlockPoint\",\"slot\":746},\"head\":{\"headerHash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"BlockPoint\",\"slot\":795}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_UID":"10016","__SEQNUM":"2492","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9bc;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=1ba66107bf4219d9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024220102","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9bd;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=4fa0df5f65b230ee","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.105240048Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"Point\",\"slot\":809},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2493","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"30943229","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024220102","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.105299552Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9be;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=e312f605dbc9f4fe","__MONOTONIC_TIMESTAMP":"30943229","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_COMM":"cardano-node","__SEQNUM":"2494","_RUNTIME_SCOPE":"system"} +{"__MONOTONIC_TIMESTAMP":"30943229","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9bf;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=810ee0894d139b96","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2495","__REALTIME_TIMESTAMP":"1761317024220102","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.105319946Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout"} +{"_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c0;b=082ebd52b7694299b9566558b64d809c;m=1d827fd;t=641e89390c3c6;x=21c04a2a732e47d9","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"30943229","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024220102","_GID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2496","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.169208233Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":746}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3"} +{"_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31024700","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024301572","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.185169759Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"BlockPoint\",\"slot\":809},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2497","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c1;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=ffd0580f558f074d","_TRANSPORT":"stdout","_GID":"10016"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c2;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=cb9caaf3570cd778","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024301572","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","__MONOTONIC_TIMESTAMP":"31024700","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","__SEQNUM":"2498","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.185380401Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07@809\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.185460578Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__SEQNUM":"2499","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31024700","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317024301572","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c3;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=1703088760259079","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024301572","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_HOSTNAME":"leios-node","_UID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"31024700","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c4;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=6a4afbe7f0174d44","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.185486001Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"Point\",\"slot\":810},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2500"} +{"_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317024301572","_COMM":"cardano-node","PRIORITY":"6","__SEQNUM":"2501","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.232328267Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"BlockPoint\",\"slot\":756},\"head\":{\"headerHash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"BlockPoint\",\"slot\":809}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_GID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"31024700","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c5;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=90687ffadeb48970"} +{"_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.232381067Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"Point\",\"slot\":810},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317024301572","__MONOTONIC_TIMESTAMP":"31024700","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__SEQNUM":"2502","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c6;b=082ebd52b7694299b9566558b64d809c;m=1d9663c;t=641e893920204;x=830e254035c24bae","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"31067704","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024344576","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2503","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.232453702Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","PRIORITY":"6","_GID":"10016","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c7;b=082ebd52b7694299b9566558b64d809c;m=1da0e38;t=641e89392aa00;x=6e5a3b16038003d4","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c8;b=082ebd52b7694299b9566558b64d809c;m=1da0e38;t=641e89392aa00;x=902f962c362bdfd3","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__SEQNUM":"2504","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024344576","__MONOTONIC_TIMESTAMP":"31067704","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.232483873Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.24834371Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":984},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317024344576","_COMM":"cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"2505","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31067704","_PID":"759","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9c9;b=082ebd52b7694299b9566558b64d809c;m=1da0e38;t=641e89392aa00;x=aca1d1cf56504e1f","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2506","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.259658556Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"BlockPoint\",\"slot\":810},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ca;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=c1e3d09ef315c925","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317024361759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"31084889","_PID":"759","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__SEQNUM":"2507","__REALTIME_TIMESTAMP":"1761317024361759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9cb;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=4884e385b2587c41","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","__MONOTONIC_TIMESTAMP":"31084889","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.259808296Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8@810\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.296086091Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9cc;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=96ce9ff8986d1d3e","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317024361759","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"31084889","__SEQNUM":"2508","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9cd;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=4eadb46668cd4d76","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.30040759Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"Point\",\"slot\":829},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317024361759","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_CAP_EFFECTIVE":"0","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"31084889","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2509","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_GID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31084889","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ce;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=5ee542c35022abe9","__REALTIME_TIMESTAMP":"1761317024361759","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","PRIORITY":"6","_CAP_EFFECTIVE":"0","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2510","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.326284342Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"adc0a33c8fc38dd9382fe7cb4038e99360efa3ac8712f613f072b1939762f9b3\",\"kind\":\"BlockPoint\",\"slot\":756}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}"} +{"_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317024361759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.326336304Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":756}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9cf;b=082ebd52b7694299b9566558b64d809c;m=1da5159;t=641e89392ed1f;x=c21f70f90d0fce95","_GID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31084889","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2511","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_PID":"759","SYSLOG_FACILITY":"3"} +{"__SEQNUM":"2512","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d0;b=082ebd52b7694299b9566558b64d809c;m=1dae198;t=641e893937d61;x=f4a4081e23f07155","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.350752257Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317024398689","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"31121816","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_GID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317024398689","__MONOTONIC_TIMESTAMP":"31121816","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.362344233Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":780}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM":"2513","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d1;b=082ebd52b7694299b9566558b64d809c;m=1dae198;t=641e893937d61;x=b1541672ea03acce","_COMM":"cardano-node","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.36830784Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"751da61a6759f89390d40d1f49fd67dcd635917aa68527be27f03f1453078b98\",\"kind\":\"BlockPoint\",\"slot\":780},\"head\":{\"headerHash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"BlockPoint\",\"slot\":810}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","__MONOTONIC_TIMESTAMP":"31137118","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d2;b=082ebd52b7694299b9566558b64d809c;m=1db1d5e;t=641e89393b921;x=d563f07e24fac7bd","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_GID":"10016","__REALTIME_TIMESTAMP":"1761317024413985","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__SEQNUM":"2514","_COMM":"cardano-node","PRIORITY":"6"} +{"PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.380004298Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":49,\"headerHash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__SEQNUM":"2515","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","__MONOTONIC_TIMESTAMP":"31137118","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d3;b=082ebd52b7694299b9566558b64d809c;m=1db1d5e;t=641e89393b921;x=d0670f78be4c0533","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317024413985","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.380043409Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31137118","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d4;b=082ebd52b7694299b9566558b64d809c;m=1db1d5e;t=641e89393b921;x=88cb7bd31a8c3095","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__SEQNUM":"2516","__REALTIME_TIMESTAMP":"1761317024413985","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3"} +{"_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31137118","_GID":"10016","PRIORITY":"6","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d5;b=082ebd52b7694299b9566558b64d809c;m=1db1d5e;t=641e89393b921;x=b797be2048b9102e","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2517","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024413985","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.38006939Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"31137118","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.380111575Z\",\"ns\":\"ChainSync.Client.DownloadedHeader\",\"data\":{\"block\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"blockNo\":51,\"kind\":\"DownloadedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slot\":994},\"sev\":\"Info\",\"thread\":\"74\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d6;b=082ebd52b7694299b9566558b64d809c;m=1db1d5e;t=641e89393b921;x=e82dc0ad82313909","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024413985","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2518","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_SLICE":"system.slice"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.38035574Z\",\"ns\":\"ChainSync.Client.WaitingBeyondForecastHorizon\",\"data\":{\"kind\":\"WaitingBeyondForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":994},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d7;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=2fd1cabe97c21794","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31177294","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2519","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024454167"} +{"_PID":"759","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.380630914Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024454167","_TRANSPORT":"stdout","__SEQNUM":"2520","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31177294","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d8;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=b660858020f3bbb2","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9d9;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=39e9e415c3736430","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.398244326Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"Point\",\"slot\":829},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024454167","__MONOTONIC_TIMESTAMP":"31177294","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_TRANSPORT":"stdout","__SEQNUM":"2521","_PID":"759"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2522","__MONOTONIC_TIMESTAMP":"31177294","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317024454167","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9da;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=39ec912b962c95bf","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.398341266Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system"} +{"_PID":"759","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__SEQNUM":"2523","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.398375628Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024454167","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9db;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=88ff8ff3c0e295ef","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31177294","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9dc;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=23fd5c759b8387c","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.398499666Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_PID":"759","__SEQNUM":"2524","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31177294","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024454167","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout"} +{"_PID":"759","_UID":"10016","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.398785177Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"31177294","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2525","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024454167","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9dd;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=2ab3205917d8164d","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024454167","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__SEQNUM":"2526","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.413682042Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"BlockPoint\",\"slot\":829},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9de;b=082ebd52b7694299b9566558b64d809c;m=1dbba4e;t=641e893945617;x=772f6083050badd5","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31177294"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317024515011","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31238164","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","__SEQNUM":"2527","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9df;b=082ebd52b7694299b9566558b64d809c;m=1dca814;t=641e8939543c3;x=4c70d3df3244a6f4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.438697512Z\",\"ns\":\"ChainSync.Client.AccessingForecastHorizon\",\"data\":{\"kind\":\"AccessingForecastHorizon\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"slotNo\":994},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_UID":"10016","_PID":"759"} +{"_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.46110008Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553@829\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e0;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=4a6fb7c2abfd7063","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_PID":"759","__SEQNUM":"2528","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"31257092","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024533960"} +{"__MONOTONIC_TIMESTAMP":"31257092","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.46125848Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2529","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e1;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=ad9433c19f549b3c","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_PID":"759","__REALTIME_TIMESTAMP":"1761317024533960","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.461290607Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"Point\",\"slot\":863},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e2;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=12524e7f88ade5f0","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"31257092","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024533960","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2530","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"31257092","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.510159947Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":795}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e3;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=ec062a4f75066ce4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024533960","_RUNTIME_SCOPE":"system","__SEQNUM":"2531","_GID":"10016","_TRANSPORT":"stdout","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759"} +{"_PID":"759","__MONOTONIC_TIMESTAMP":"31257092","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.510551337Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToVolatileDB\",\"data\":{\"block\":{\"hash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"Point\",\"slot\":863},\"blockNo\":\"47\",\"kind\":\"AddedBlockToVolatileDB\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e4;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=393fb6ddbe638867","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317024533960","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2532","SYSLOG_FACILITY":"3"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:44.511849826Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0e45f814b59556a26c9a9f0c4d168a94265a11084ab2337a24350d19e6ac757a\",\"kind\":\"BlockPoint\",\"slot\":795},\"head\":{\"headerHash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"BlockPoint\",\"slot\":829}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"31257092","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e5;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=7fa0ba7cef163614","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317024533960","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__SEQNUM":"2533","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__SEQNUM":"2534","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.512002639Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"Point\",\"slot\":863},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_PID":"759","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31257092","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e6;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=2ab7cdbe5cecc19f","_UID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","PRIORITY":"6","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024533960","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024533960","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_PID":"759","__SEQNUM":"2535","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.512092036Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a@863\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e7;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=77b00b87739d9f6f","__MONOTONIC_TIMESTAMP":"31257092","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.512127236Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a@863\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024533960","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e8;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=244b82a93eca6a43","__MONOTONIC_TIMESTAMP":"31257092","__SEQNUM":"2536","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice"} +{"_TRANSPORT":"stdout","PRIORITY":"6","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2537","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"31257092","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024533960","_RUNTIME_SCOPE":"system","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9e9;b=082ebd52b7694299b9566558b64d809c;m=1dcf204;t=641e893958dc8;x=bf776d28cb41327","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.514738182Z\",\"ns\":\"ChainSync.Client.ValidatedHeader\",\"data\":{\"headerHash\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"ValidatedHeader\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ea;b=082ebd52b7694299b9566558b64d809c;m=1de1031;t=641e89396abf3;x=ab233f434cdffae1","__MONOTONIC_TIMESTAMP":"31330353","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.51487088Z\",\"ns\":\"ChainSync.Client.GaveLoPToken\",\"data\":{\"blockNo\":50,\"headerHash\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"TraceGaveLoPToken\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"tokenAdded\":true},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024607219","__SEQNUM":"2538","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2539","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"31341599","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9eb;b=082ebd52b7694299b9566558b64d809c;m=1de3c1f;t=641e89396d7e8;x=1b0f5390dce27549","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024618472","_COMM":"cardano-node","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.52114151Z\",\"ns\":\"ChainSync.Client.JumpingWaitingForNextInstruction\",\"data\":{\"kind\":\"TraceJumpingWaitingForNextInstruction\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2540","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024625546","__MONOTONIC_TIMESTAMP":"31348674","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.52165191Z\",\"ns\":\"ChainSync.Client.JumpingInstructionIs\",\"data\":{\"instr\":{\"kind\":\"RunNormally\"},\"kind\":\"TraceJumpingInstructionIs\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Debug\",\"thread\":\"74\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ec;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=cc8bb7aa48993e09","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.522487212Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317024625546","__MONOTONIC_TIMESTAMP":"31348674","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ed;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=6d3cf1a017e7d525","__SEQNUM":"2541"} +{"_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31348674","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__SEQNUM":"2542","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","__REALTIME_TIMESTAMP":"1761317024625546","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.523208812Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedBlockToQueue\",\"data\":{\"block\":{\"hash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"Point\",\"slot\":984},\"kind\":\"AddedBlockToQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"67\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ee;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=17486609cd3fb9a3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node"} +{"_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.523345701Z\",\"ns\":\"BlockFetch.Client.CompletedBlockFetch\",\"data\":{\"block\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"delay\":1363426.523080304,\"kind\":\"CompletedBlockFetch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"},\"size\":864},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317024625546","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__MONOTONIC_TIMESTAMP":"31348674","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","PRIORITY":"6","__SEQNUM":"2543","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ef;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=c5006c5349ca3c5","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f0;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=2c08618d3a124bfc","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_COMM":"cardano-node","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.523427275Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024625546","_HOSTNAME":"leios-node","PRIORITY":"6","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2544","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31348674","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"31348674","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024625546","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_PID":"759","_HOSTNAME":"leios-node","_UID":"10016","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.527647923Z\",\"ns\":\"BlockFetch.Client.AcknowledgedFetchRequest\",\"data\":{\"kind\":\"AcknowledgedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","__SEQNUM":"2545","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f1;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=8d644c67bcb639f4","_CAP_EFFECTIVE":"0"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2546","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f2;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=29c6bc5bdad4f511","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"31348674","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_GID":"10016","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.527465498Z\",\"ns\":\"BlockFetch.Client.AddedFetchRequest\",\"data\":{\"kind\":\"AddedFetchRequest\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"34\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024625546","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_PID":"759"} +{"_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","PRIORITY":"6","__SEQNUM":"2547","__MONOTONIC_TIMESTAMP":"31348674","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024625546","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f3;b=082ebd52b7694299b9566558b64d809c;m=1de57c2;t=641e89396f38a;x=f96a1f59e384307c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.52826113Z\",\"ns\":\"BlockFetch.Client.SendFetchRequest\",\"data\":{\"head\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"SendFetchRequest\",\"length\":1,\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"68\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024680020","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.552723457Z\",\"ns\":\"BlockFetch.Client.StartedFetchBatch\",\"data\":{\"kind\":\"StartedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","__SEQNUM":"2548","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f4;b=082ebd52b7694299b9566558b64d809c;m=1df2c8f;t=641e89397c854;x=62560d0e72b73a81","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31403151","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node"} +{"SYSLOG_FACILITY":"3","_PID":"759","__REALTIME_TIMESTAMP":"1761317024691960","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f5;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=60868ef62ab2acfb","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.558334784Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"BlockPoint\",\"slot\":863},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"31415090","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2549","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","__SEQNUM":"2550","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.558510505Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a@863\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f6;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=e6d3a8025a0b52fe","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"31415090","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_UID":"10016","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__REALTIME_TIMESTAMP":"1761317024691960","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f7;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=53c4c189a6f8f500","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024691960","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.558591242Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","_GID":"10016","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"31415090","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2551","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317024691960","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"31415090","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2552","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f8;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=87e74bf3276227fc","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.558616384Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"Point\",\"slot\":887},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9f9;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=a5b18aa04602a06e","__REALTIME_TIMESTAMP":"1761317024691960","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31415090","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2553","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.582597365Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"d4b3efb3c53a2adc32dc852599ad7da9d00507c4c81872f6a90f449d9d724d07\",\"kind\":\"BlockPoint\",\"slot\":809},\"head\":{\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"BlockPoint\",\"slot\":863}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_COMM":"cardano-node","__SEQNUM":"2554","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.582699892Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"Point\",\"slot\":887},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024691960","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9fa;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=bfc1ff1625414f83","_UID":"10016","__MONOTONIC_TIMESTAMP":"31415090","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node"} +{"_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317024691960","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9fb;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=55a5387b7a9b3fe1","__SEQNUM":"2555","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.582792083Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369@887\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31415090"} +{"_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9fc;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=368e93490b85ac1","_UID":"10016","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.5828284Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369@887\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"31415090","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317024691960","__SEQNUM":"2556"} +{"__SEQNUM":"2557","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024691960","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9fd;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=d9b463e36298115e","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"31415090","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.650251494Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":809}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}"} +{"_CAP_EFFECTIVE":"0","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317024691960","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31415090","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.650408498Z\",\"ns\":\"BlockFetch.Client.CompletedFetchBatch\",\"data\":{\"kind\":\"CompletedFetchBatch\",\"peer\":{\"connectionId\":\"192.168.1.2:3001 192.168.1.1:3001\"}},\"sev\":\"Info\",\"thread\":\"67\",\"host\":\"leios-node\"}","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2558","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9fe;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=d8765e8b19d68d28"} +{"_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.650757704Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"BlockPoint\",\"slot\":887},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"31415090","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=9ff;b=082ebd52b7694299b9566558b64d809c;m=1df5b32;t=641e89397f6f8;x=48fe463734e25a3e","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2559","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024691960","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_HOSTNAME":"leios-node","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__SEQNUM":"2560","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317024757533","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a00;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=45c3fd84a638da2d","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.676749834Z\",\"ns\":\"ChainDB.AddBlockEvent.AddedToCurrentChain\",\"data\":{\"kind\":\"AddedToCurrentChain\",\"newTipSelectView\":{\"chainLength\":48,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":887,\"tieBreakVRF\":\"55738ba18e6473228a5bfd57a384c231d2fc95a32a92231fc28f8740d3663186bb56b73d8af280eac8a2f85770e24d8d7c0e1347f862d7ffac92dc261258e0dd\"},\"newtip\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369@887\",\"oldTipSelectView\":{\"chainLength\":47,\"issueNo\":0,\"issuerHash\":\"68b23036da5530e5853357a8dc9d03dd8e851b0e29a3eaf61b55b6cc\",\"kind\":\"PraosChainSelectView\",\"slotNo\":863,\"tieBreakVRF\":\"3aa5b90e32792498223abe978bb79e751c635827ab964e0d0b1bde2a6f6af76b1763f3a5dcd4941bdd5edfd0b0b3c29a3f84dbd04b47cca6b72172d1572640af\"}},\"sev\":\"Notice\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_GID":"10016","__MONOTONIC_TIMESTAMP":"31480661","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_PID":"759","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31480661","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024757533","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.686320604Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369@887\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM":"2561","_COMM":"cardano-node","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a01;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=17720e838b06fb26","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.686454699Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2562","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024757533","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a02;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=cd7ea4adf008535","__MONOTONIC_TIMESTAMP":"31480661","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a03;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=14b8cacdee8f7f0c","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.686492972Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"Point\",\"slot\":907},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","__SEQNUM":"2563","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_GID":"10016","__MONOTONIC_TIMESTAMP":"31480661","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317024757533","_TRANSPORT":"stdout"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"31480661","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.688651068Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":810}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a04;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=4bfb44816c2c721b","_COMM":"cardano-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","__SEQNUM":"2564","_HOSTNAME":"leios-node","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024757533","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__REALTIME_TIMESTAMP":"1761317024757533","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"31480661","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.689552858Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"de8f9b6128f069ccc8ebc2aab764d4a5f95a50c18158292b242b83516dc755e8\",\"kind\":\"BlockPoint\",\"slot\":810},\"head\":{\"headerHash\":\"10f25596ed73a9201d2f2b9b1449c69a2e049d03e913796d62c3a2736faaf369\",\"kind\":\"BlockPoint\",\"slot\":887}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a05;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=c237fa1c99656984","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2565"} +{"_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__SEQNUM":"2566","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024757533","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.689596439Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"Point\",\"slot\":907},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"31480661","_PID":"759","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a06;b=082ebd52b7694299b9566558b64d809c;m=1e05b55;t=641e89398f71d;x=849935c52f85cd95","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2567","__MONOTONIC_TIMESTAMP":"31529357","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024806229","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.689653988Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328@907\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a07;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=ea07464b9aaa02c6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2568","__REALTIME_TIMESTAMP":"1761317024806229","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_COMM":"cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"31529357","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.689674661Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328@907\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a08;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=143377dde86a9656"} +{"_PID":"759","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.747423062Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"BlockPoint\",\"slot\":907},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a09;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=cc2936f85c490661","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31529357","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2569","__REALTIME_TIMESTAMP":"1761317024806229","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0a;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=4ea8fa93eb066ecb","_PID":"759","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.747592637Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328@907\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2570","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317024806229","_UID":"10016","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"31529357","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node"} +{"_HOSTNAME":"leios-node","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"31529357","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","__SEQNUM":"2571","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317024806229","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0b;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=348b75e92e00162f","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.747673374Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_TRANSPORT":"stdout","_GID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2572","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.747700472Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"Point\",\"slot\":984},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317024806229","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_PID":"759","__MONOTONIC_TIMESTAMP":"31529357","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0c;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=913445b91c5084c3","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0d;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=eab0c9f61a58e6ec","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31529357","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.777542254Z\",\"ns\":\"Net.Server.Local.AcceptConnection\",\"data\":{\"address\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"AcceptConnection\"},\"sev\":\"Debug\",\"thread\":\"48\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2573","__REALTIME_TIMESTAMP":"1761317024806229","SYSLOG_FACILITY":"3","_GID":"10016","_RUNTIME_SCOPE":"system","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016"} +{"_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0e;b=082ebd52b7694299b9566558b64d809c;m=1e1198d;t=641e89399b555;x=4fa91d39a3918ab4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"31529357","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.799799272Z\",\"ns\":\"Net.ConnectionManager.Local.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Inbound\",\"remoteAddress\":{\"path\":\"/run/cardano-node/node.socket@3\"}},\"sev\":\"Debug\",\"thread\":\"99\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024806229","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2574","_TRANSPORT":"stdout"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a0f;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=99819c16ef7908b6","_PID":"759","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31573792","_COMM":"cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.812350029Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":829}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024850664","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2575","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317024850664","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31573792","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a10;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=ae36a11590597c28","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.812563185Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"41355105041929d14e917e6af30ac882534d46ec9268fc2677c358478cb66553\",\"kind\":\"BlockPoint\",\"slot\":829},\"head\":{\"headerHash\":\"dc8bb970f0aa5cd8213bb0fd0a835a52591702d2269b398876c6eea6b18e3328\",\"kind\":\"BlockPoint\",\"slot\":907}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","PRIORITY":"6","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","_GID":"10016","SYSLOG_FACILITY":"3","_UID":"10016","__SEQNUM":"2576","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node"} +{"_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a11;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=9cb7ad2c28cf3823","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2577","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317024850664","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"31573792","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_FACILITY":"3","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.812600061Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"Point\",\"slot\":984},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node"} +{"PRIORITY":"6","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.812655096Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02@984\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2578","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a12;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=5eeb9d656ad00119","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317024850664","_UID":"10016","__MONOTONIC_TIMESTAMP":"31573792","_GID":"10016","_RUNTIME_SCOPE":"system","_PID":"759"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a13;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=ff681d1fddf4a79d","__MONOTONIC_TIMESTAMP":"31573792","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2579","SYSLOG_FACILITY":"3","PRIORITY":"6","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317024850664","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.81267996Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02@984\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","PRIORITY":"6","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024850664","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31573792","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2580","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a14;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=7f6dee2f6c0468e0","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.812797572Z\",\"ns\":\"Net.Handshake.Local.Receive.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@3\\\"}\",\"event\":\"Recv AnyMessage MsgProposeVersions (fromList [(NodeToClientV_16,TList [TInt 42,TBool False]),(NodeToClientV_17,TList [TInt 42,TBool False]),(NodeToClientV_18,TList [TInt 42,TBool False]),(NodeToClientV_19,TList [TInt 42,TBool False]),(NodeToClientV_20,TList [TInt 42,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"100\",\"host\":\"leios-node\"}","_PID":"759"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317024850664","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a15;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=ae756076b6704178","__SEQNUM":"2581","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.844705818Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":318392640,\"CentiBlkIO\":0,\"CentiCpu\":126,\"CentiGC\":2,\"CentiMut\":117,\"FsRd\":50929664,\"FsWr\":385024,\"GcsMajor\":2,\"GcsMinor\":8,\"Heap\":49283072,\"Live\":4769648,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_PID":"759","__MONOTONIC_TIMESTAMP":"31573792","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.84955839Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"99\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024850664","__MONOTONIC_TIMESTAMP":"31573792","SYSLOG_FACILITY":"3","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a16;b=082ebd52b7694299b9566558b64d809c;m=1e1c720;t=641e8939a62e8;x=54b9eff6f9090430","__SEQNUM":"2582","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2583","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__REALTIME_TIMESTAMP":"1761317024910311","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.867682481Z\",\"ns\":\"Net.Handshake.Local.Send.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@3\\\"}\",\"event\":\"Send AnyMessage MsgAcceptVersion NodeToClientV_20 (TList [TInt 42,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"100\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a17;b=082ebd52b7694299b9566558b64d809c;m=1e2b01e;t=641e8939b4be7;x=3db8709cb5478a45","_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31633438","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","_GID":"10016"} +{"_HOSTNAME":"leios-node","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.86774003Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"networkMagic\":42,\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":20},\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"100\",\"host\":\"leios-node\"}","__SEQNUM":"2584","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"31633438","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a18;b=082ebd52b7694299b9566558b64d809c;m=1e2b01e;t=641e8939b4be7;x=8fe5ad07a3f5fd5","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317024910311","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system"} +{"__SEQNUM":"2585","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.876026279Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"99\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317024910311","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"31633438","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","_COMM":"cardano-node","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a19;b=082ebd52b7694299b9566558b64d809c;m=1e2b01e;t=641e8939b4be7;x=46b5da83b19cedfc","_CAP_EFFECTIVE":"0"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2586","_CAP_EFFECTIVE":"0","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.909345038Z\",\"ns\":\"Net.InboundGovernor.Local.NewConnection\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"NewConnection\",\"provenance\":\"Inbound\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1a;b=082ebd52b7694299b9566558b64d809c;m=1e2b01e;t=641e8939b4be7;x=a0d25c776845a6c2","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__REALTIME_TIMESTAMP":"1761317024910311","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"31633438","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"31664112","_HOSTNAME":"leios-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.909434994Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_GID":"10016","__SEQNUM":"2587","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1b;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=e0249d21057e9cb5","_TRANSPORT":"stdout","_UID":"10016","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317024940980","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2588","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31664112","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","__REALTIME_TIMESTAMP":"1761317024940980","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.909470473Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1c;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=5fda36527c98793d","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_GID":"10016"} +{"_HOSTNAME":"leios-node","_UID":"10016","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317024940980","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918011782Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"BlockPoint\",\"slot\":984},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1d;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=71bb6cd6cd70cf09","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","__MONOTONIC_TIMESTAMP":"31664112","__SEQNUM":"2589","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3"} +{"_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"31664112","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918209852Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02@984\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1e;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=5b534ab2286fb9cf","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_PID":"759","_GID":"10016","__SEQNUM":"2590","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024940980","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_RUNTIME_SCOPE":"system","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918293662Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"31664112","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024940980","_CAP_EFFECTIVE":"0","__SEQNUM":"2591","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a1f;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=95a7459e2a7654e4","_COMM":"cardano-node","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918318805Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"block\":{\"hash\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"Point\",\"slot\":994},\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31664112","_UID":"10016","__SEQNUM":"2592","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a20;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=25e1dfe7164433cd","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317024940980","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_SYSTEMD_SLICE":"system.slice","PRIORITY":"6","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a21;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=8e677ca0c35e332a","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317024940980","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"31664112","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918590627Z\",\"ns\":\"ChainDB.AddBlockEvent.ChainSelectionLoEDebug\",\"data\":{\"curChain\":{\"anchor\":{\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"BlockPoint\",\"slot\":863},\"head\":{\"headerHash\":\"6a474a35b64314bdc4b3908bf889d91151896307cef3e6e4b6862c93a83e5c02\",\"kind\":\"BlockPoint\",\"slot\":984}},\"kind\":\"ChainSelectionLoEDebug\",\"loeFrag\":\"LoE is disabled\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_GID":"10016","__SEQNUM":"2593","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_COMM":"cardano-node"} +{"SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2594","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"31664112","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a22;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=81e869eef0aa0f78","_GID":"10016","_TRANSPORT":"stdout","PRIORITY":"6","_PID":"759","__REALTIME_TIMESTAMP":"1761317024940980","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918624151Z\",\"ns\":\"ChainDB.AddBlockEvent.TryAddToCurrentChain\",\"data\":{\"block\":{\"hash\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"Point\",\"slot\":994},\"kind\":\"TryAddToCurrentChain\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_COMM":"cardano-node","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317024940980","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_RUNTIME_SCOPE":"system","__SEQNUM":"2595","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918676671Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc@994\",\"kind\":\"SetTentativeHeader\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a23;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=1119ed399a802d0d","_UID":"10016","__MONOTONIC_TIMESTAMP":"31664112"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a24;b=082ebd52b7694299b9566558b64d809c;m=1e327f0;t=641e8939bc3b4;x=c24d58ce69f714e7","_COMM":"cardano-node","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2596","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.918697065Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader\",\"data\":{\"block\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc@994\",\"kind\":\"SetTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_PID":"759","_UID":"10016","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317024940980","__MONOTONIC_TIMESTAMP":"31664112","_CAP_EFFECTIVE":"0","_GID":"10016"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a25;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=d877caf8780fc9d5","__MONOTONIC_TIMESTAMP":"31734108","_RUNTIME_SCOPE":"system","_UID":"10016","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.940766071Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317025010980","_HOSTNAME":"leios-node","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2597","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.940805182Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToWarmRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"PromotedToWarmRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundIdleSt\"}}},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a26;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=771476846d5b5976","_RUNTIME_SCOPE":"system","_CAP_EFFECTIVE":"0","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"31734108","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317025010980","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2598","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout"} +{"_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.940838985Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":1},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2599","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"31734108","__REALTIME_TIMESTAMP":"1761317025010980","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a27;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=74144ba7491ab308","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_PID":"759","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","PRIORITY":"6"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a28;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=95abee56ef90a93e","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317025010980","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_COMM":"cardano-node","__SEQNUM":"2600","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.940948776Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"RemoteWarmSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6","_PID":"759","_GID":"10016","__MONOTONIC_TIMESTAMP":"31734108","_CAP_EFFECTIVE":"0"} +{"__REALTIME_TIMESTAMP":"1761317025010980","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.989041201Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToHotRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"PromotedToHotRemote\"},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_SLICE":"system.slice","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31734108","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__SEQNUM":"2601","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a29;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=fffddfb6e5618a22","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service"} +{"_PID":"759","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317025010980","_CAP_EFFECTIVE":"0","__SEQNUM":"2602","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.989067182Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":1,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"31734108","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2a;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=9b429e3bd841c45f","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","SYSLOG_FACILITY":"3","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"31734108","MESSAGE":"{\"at\":\"2025-10-24T14:43:44.989088972Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"RemoteHotSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_RUNTIME_SCOPE":"system","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2b;b=082ebd52b7694299b9566558b64d809c;m=1e4395c;t=641e8939cd524;x=392774b8c7fb0462","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2603","__REALTIME_TIMESTAMP":"1761317025010980"} +{"__SEQNUM":"2604","_PID":"759","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2c;b=082ebd52b7694299b9566558b64d809c;m=1e4ec8e;t=641e8939d8856;x=6b13a944b65a697c","__REALTIME_TIMESTAMP":"1761317025056854","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.009345178Z\",\"ns\":\"StateQueryServer.Receive.Acquire\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgAcquire\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31779982","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2605","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2d;b=082ebd52b7694299b9566558b64d809c;m=1e4ec8e;t=641e8939d8856;x=8344848928ae9bff","__REALTIME_TIMESTAMP":"1761317025056854","__MONOTONIC_TIMESTAMP":"31779982","_COMM":"cardano-node","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"TraceObject queue overflowed. Dropped 128 messages from 2025-10-24 14:43:43.978033377 UTC to 2025-10-24 14:43:45.056244994 UTC","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2e;b=082ebd52b7694299b9566558b64d809c;m=1e5155e;t=641e8939db124;x=72f445d4c6872e8e","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"31790430","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.039799607Z\",\"ns\":\"ChainDB.CopyToImmutableDBEvent.CopiedBlockToImmutableDB\",\"data\":{\"kind\":\"CopiedBlockToImmutableDB\",\"slot\":{\"headerHash\":\"0d0e583d7c169f7d0de3ccfe7bacbff35833ec43d877dc623d855cecd920591a\",\"kind\":\"BlockPoint\",\"slot\":863}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317025067300","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2606","_TRANSPORT":"stdout","_GID":"10016","_CAP_EFFECTIVE":"0","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"__REALTIME_TIMESTAMP":"1761317025067300","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31790430","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a2f;b=082ebd52b7694299b9566558b64d809c;m=1e5155e;t=641e8939db124;x=43f2ccc017fa7503","_PID":"759","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2607","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.049755901Z\",\"ns\":\"ChainDB.AddBlockEvent.ChangingSelection\",\"data\":{\"block\":{\"headerHash\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc\",\"kind\":\"BlockPoint\",\"slot\":994},\"kind\":\"TraceAddBlockEvent.ChangingSelection\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_RUNTIME_SCOPE":"system","__SEQNUM":"2608","__MONOTONIC_TIMESTAMP":"31790430","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.056142746Z\",\"ns\":\"ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader\",\"data\":{\"block\":\"6685f44f32433d0817b6edf5f9e00aaaa3c4986524b8b453a620825747a936cc@994\",\"kind\":\"OutdatedTentativeHeader\"},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a30;b=082ebd52b7694299b9566558b64d809c;m=1e5155e;t=641e8939db124;x=5953096bb82781dc","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","__REALTIME_TIMESTAMP":"1761317025067300","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a31;b=082ebd52b7694299b9566558b64d809c;m=1e5155e;t=641e8939db124;x=1cc2f38daa73c1f9","__MONOTONIC_TIMESTAMP":"31790430","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2609","__REALTIME_TIMESTAMP":"1761317025067300","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_COMM":"cardano-node","_GID":"10016","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.056244994Z\",\"ns\":\"ChainDB.AddBlockEvent.PoppedBlockFromQueue\",\"data\":{\"kind\":\"TraceAddBlockEvent.PoppedBlockFromQueue\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"31821843","__REALTIME_TIMESTAMP":"1761317025098713","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","__SEQNUM":"2610","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.05627293Z\",\"ns\":\"ChainDB.ChainSelStarvationEvent\",\"data\":{\"kind\":\"ChainSelStarvation\",\"risingEdge\":true},\"sev\":\"Debug\",\"thread\":\"20\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a32;b=082ebd52b7694299b9566558b64d809c;m=1e59013;t=641e8939e2bd9;x=e1d4e62853c28244","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016"} +{"__REALTIME_TIMESTAMP":"1761317025098713","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a33;b=082ebd52b7694299b9566558b64d809c;m=1e59013;t=641e8939e2bd9;x=bb3208ae3700a1db","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.039930909Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":863}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__MONOTONIC_TIMESTAMP":"31821843","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2611","_GID":"10016"} +{"__SEQNUM":"2612","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a34;b=082ebd52b7694299b9566558b64d809c;m=1e59013;t=641e8939e2bd9;x=e973eee08cadd90c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317025098713","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.084567308Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"31821843","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"__REALTIME_TIMESTAMP":"1761317025098713","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a35;b=082ebd52b7694299b9566558b64d809c;m=1e59013;t=641e8939e2bd9;x=cf61fc7d08c6023b","__SEQNUM":"2613","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_GID":"10016","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.08565348Z\",\"ns\":\"ChainDB.GCEvent.ScheduledGC\",\"data\":{\"kind\":\"ScheduledGC\",\"slot\":{\"kind\":\"SlotNo\",\"slot\":887}},\"sev\":\"Debug\",\"thread\":\"24\",\"host\":\"leios-node\"}","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"31821843","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","__MONOTONIC_TIMESTAMP":"31842326","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_PID":"759","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.098631386Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a36;b=082ebd52b7694299b9566558b64d809c;m=1e5e016;t=641e8939e7bda;x=f94b8a2fb2993033","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","__SEQNUM":"2614","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317025119194","_RUNTIME_SCOPE":"system"} +{"_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317025127942","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_COMM":"cardano-node","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a37;b=082ebd52b7694299b9566558b64d809c;m=1e6023f;t=641e8939e9e06;x=95e339ede6137860","__SEQNUM":"2615","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.127183618Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"31851071","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"MESSAGE":"{\"at\":\"2025-10-24T14:43:45.136038375Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_GID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a38;b=082ebd52b7694299b9566558b64d809c;m=1e627a9;t=641e8939ec36b;x=c31e0de1291cd1b5","__SEQNUM":"2616","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317025137515","_CAP_EFFECTIVE":"0","__MONOTONIC_TIMESTAMP":"31860649","_COMM":"cardano-node"} +{"__SEQNUM":"2617","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_GID":"10016","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.144124319Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"31867816","__REALTIME_TIMESTAMP":"1761317025144688","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a39;b=082ebd52b7694299b9566558b64d809c;m=1e643a8;t=641e8939edf70;x=b57081c118cbcf4f","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2618","__MONOTONIC_TIMESTAMP":"31876668","_PID":"759","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3a;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=d59ed50c0cb7c733","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317025153537","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151268803Z\",\"ns\":\"StateQueryServer.Receive.Release\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgRelease\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}"} +{"_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3b;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=3a32c220aed05a67","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2619","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151321882Z\",\"ns\":\"StateQueryServer.Receive.Done\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgDone\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"}},\"sev\":\"Info\",\"thread\":\"103\",\"host\":\"leios-node\"}","_UID":"10016","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31876668","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","_PID":"759","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317025153537","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3c;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=6400bfc44cc77d94","__REALTIME_TIMESTAMP":"1761317025153537","__SEQNUM":"2620","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"31876668","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151407647Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_UID":"10016"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151428879Z\",\"ns\":\"Net.InboundGovernor.Local.WaitIdleRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"WaitIdleRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundSt\"}}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__REALTIME_TIMESTAMP":"1761317025153537","_RUNTIME_SCOPE":"system","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3d;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=d659aacef7c11abd","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_UID":"10016","__MONOTONIC_TIMESTAMP":"31876668","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","__SEQNUM":"2621","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"__SEQNUM":"2622","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151453463Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_GID":"10016","_UID":"10016","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__MONOTONIC_TIMESTAMP":"31876668","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3e;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=65ad3d32d68d19de","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317025153537"} +{"_SYSTEMD_UNIT":"cardano-node.service","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151478047Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","PRIORITY":"6","__MONOTONIC_TIMESTAMP":"31876668","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2623","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a3f;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=700d3f60c8025016","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_PID":"759","__REALTIME_TIMESTAMP":"1761317025153537"} +{"PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_FACILITY":"3","_UID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM":"2624","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a40;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=c373f1e0e64020d6","__REALTIME_TIMESTAMP":"1761317025153537","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151531406Z\",\"ns\":\"Net.InboundGovernor.Local.ResponderRestarted\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"ResponderStarted\",\"miniProtocolNum\":{\"kind\":\"MiniProtocolNum\",\"num\":7}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"31876668","_GID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2625","_PID":"759","_GID":"10016","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317025153537","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a41;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=7b27f551970a8602","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"31876668","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_HOSTNAME":"leios-node","_RUNTIME_SCOPE":"system","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.151550961Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout"} +{"__MONOTONIC_TIMESTAMP":"31876668","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_CAP_EFFECTIVE":"0","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.15160432Z\",\"ns\":\"Net.Mux.Local.CleanExit\",\"data\":{\"bearer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@3\\\"\"},\"event\":{\"kind\":\"Mux.TraceCleanExit\",\"miniProtocolDir\":\"ResponderDir\",\"miniProtocolNum\":\"MiniProtocolNum 7\",\"msg\":\"Miniprotocol terminated cleanly\"},\"kind\":\"Mux.Trace\"},\"sev\":\"Notice\",\"thread\":\"100\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a42;b=082ebd52b7694299b9566558b64d809c;m=1e6663c;t=641e8939f0201;x=78a7294daa224111","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317025153537","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_GID":"10016","_PID":"759","__SEQNUM":"2626","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","__SEQNUM":"2627","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a43;b=082ebd52b7694299b9566558b64d809c;m=1f0f8f2;t=641e893a994b9;x=2ebc6ee9447c8c7e","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:45.846296802Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":318392640,\"CentiBlkIO\":0,\"CentiCpu\":128,\"CentiGC\":2,\"CentiMut\":119,\"FsRd\":50929664,\"FsWr\":409600,\"GcsMajor\":2,\"GcsMinor\":8,\"Heap\":49283072,\"Live\":4769648,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"32569586","_PID":"759","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317025846457","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a44;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=f8f72eaa63d0f895","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2628","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_GID":"10016","_CAP_EFFECTIVE":"0","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","__MONOTONIC_TIMESTAMP":"32856092","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.131876952Z\",\"ns\":\"Net.PeerSelection.Selection.GovernorWakeup\",\"data\":{\"kind\":\"GovernorWakeup\"},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","__REALTIME_TIMESTAMP":"1761317026132967"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132030603Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersRequest\",\"data\":{\"kind\":\"BigLedgerPeersRequest\",\"numberOfBigLedgerPeers\":0,\"targetNumberOfBigLedgerPeers\":15},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_UID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"32856092","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","_HOSTNAME":"leios-node","_PID":"759","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a45;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=ac33f9c7de4a0656","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2629","PRIORITY":"6","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317026132967","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317026132967","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a46;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=6a1c198dbe5e5761","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132115251Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsRequest\",\"data\":{\"kind\":\"PublicRootsRequest\",\"numberOfRootPeers\":1,\"targetNumberOfRootPeers\":60},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_UID":"10016","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_PID":"759","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","__SEQNUM":"2630","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"32856092","_RUNTIME_SCOPE":"system"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a47;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=9f48524f5348c319","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132148495Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317026132967","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_UID":"10016","__SEQNUM":"2631","__MONOTONIC_TIMESTAMP":"32856092","SYSLOG_IDENTIFIER":"cardano-node-start","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_CAP_EFFECTIVE":"0","_PID":"759"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026132967","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132160508Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":15},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","__SEQNUM":"2632","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a48;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=aca88e33058f2580","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","_GID":"10016","_RUNTIME_SCOPE":"system","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"32856092","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9"} +{"_PID":"759","__MONOTONIC_TIMESTAMP":"32856092","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CAP_EFFECTIVE":"0","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132177549Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":32.85528918,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2633","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a49;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=aa3de67578937e19","__REALTIME_TIMESTAMP":"1761317026132967","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","_GID":"10016"} +{"_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132189003Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM":"2634","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4a;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=dfa06631c8739477","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_GID":"10016","__MONOTONIC_TIMESTAMP":"32856092","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317026132967","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_UID":"10016"} +{"SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317026132967","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","__SEQNUM":"2635","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","__MONOTONIC_TIMESTAMP":"32856092","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4b;b=082ebd52b7694299b9566558b64d809c;m=1f5581c;t=641e893adf3e7;x=bcabb553c8e27bec","_PID":"759","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132213867Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"105\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"__REALTIME_TIMESTAMP":"1761317026160143","__MONOTONIC_TIMESTAMP":"32883269","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.13273181Z\",\"ns\":\"Net.Peers.Ledger.TraceUseLedgerPeers\",\"data\":{\"kind\":\"UseLedgerPeers\",\"useLedgerPeers\":-1},\"sev\":\"Info\",\"thread\":\"49\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4c;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=6a7fad7069ab1a0a","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","PRIORITY":"6","_CAP_EFFECTIVE":"0","__SEQNUM":"2636","SYSLOG_FACILITY":"3","_PID":"759","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"32883269","_GID":"10016","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132748571Z\",\"ns\":\"Net.Peers.Ledger.RequestForPeers\",\"data\":{\"kind\":\"RequestForPeers\",\"numberOfPeers\":59},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2637","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4d;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=1ceeb203dc03cd5e","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026160143","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","_UID":"10016"} +{"_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","__SEQNUM":"2638","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4e;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=2ce31f504756d692","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","PRIORITY":"6","_CAP_EFFECTIVE":"0","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132765613Z\",\"ns\":\"Net.Peers.Ledger.ReusingLedgerState\",\"data\":{\"kind\":\"ReusingLedgerState\",\"ledgerStateAge\":32.855878361,\"numberOfPools\":0},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317026160143","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","__MONOTONIC_TIMESTAMP":"32883269","_TRANSPORT":"stdout","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3"} +{"_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132776229Z\",\"ns\":\"Net.Peers.Ledger.WaitingOnRequest\",\"data\":{\"kind\":\"WaitingOnRequest\"},\"sev\":\"Debug\",\"thread\":\"49\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"32883269","_PID":"759","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","_TRANSPORT":"stdout","__REALTIME_TIMESTAMP":"1761317026160143","PRIORITY":"6","__SEQNUM":"2639","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a4f;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=c5497e1ac3d7dbba","_GID":"10016"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"32883269","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a50;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=99e6471e44d4a323","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2640","_UID":"10016","__REALTIME_TIMESTAMP":"1761317026160143","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_PID":"759","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.132795784Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"104\",\"host\":\"leios-node\"}"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_RUNTIME_SCOPE":"system","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__MONOTONIC_TIMESTAMP":"32883269","SYSLOG_IDENTIFIER":"cardano-node-start","SYSLOG_FACILITY":"3","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a51;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=b728e4e1888f358e","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","__SEQNUM":"2641","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","_GID":"10016","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317026160143","_COMM":"cardano-node","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.137258921Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"104\",\"host\":\"leios-node\"}"} +{"_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.141813131Z\",\"ns\":\"Net.Peers.PublicRoot.PublicRootRelayAccessPoint\",\"data\":{\"kind\":\"PublicRootRelayAddresses\",\"relayAddresses\":[]},\"sev\":\"Info\",\"thread\":\"105\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"32883269","_COMM":"cardano-node","_PID":"759","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317026160143","_GID":"10016","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a52;b=082ebd52b7694299b9566558b64d809c;m=1f5c245;t=641e893ae5e0f;x=82f93de8fa7995e8","__SEQNUM":"2642"} +{"PRIORITY":"6","_GID":"10016","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"32908705","__REALTIME_TIMESTAMP":"1761317026185578","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2643","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a53;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=1c75d64a6022e052","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.156787381Z\",\"ns\":\"Net.PeerSelection.Selection.PublicRootsResults\",\"data\":{\"diffTime\":8,\"group\":3,\"kind\":\"PublicRootsResults\",\"result\":{\"bigLedgerPeers\":[],\"bootstrapPeers\":[],\"kind\":\"PublicRootPeers\",\"ledgerPeers\":[],\"publicConfigPeers\":[]}},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_UID":"10016","__MONOTONIC_TIMESTAMP":"32908705","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317026185578","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.162836194Z\",\"ns\":\"Net.InboundGovernor.Local.MuxCleanExit\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"MuxCleanExit\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a54;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=9c3941f0565060d9","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2644","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_HOSTNAME":"leios-node"} +{"_HOSTNAME":"leios-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_PID":"759","_SYSTEMD_SLICE":"system.slice","__MONOTONIC_TIMESTAMP":"32908705","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317026185578","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","__SEQNUM":"2645","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a55;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=4c69cac7ceeb16af","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.162923356Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}"} +{"__SEQNUM":"2646","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.162952969Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a56;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=6aa998c4e578af35","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__REALTIME_TIMESTAMP":"1761317026185578","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_TRANSPORT":"stdout","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","SYSLOG_FACILITY":"3","__MONOTONIC_TIMESTAMP":"32908705","_RUNTIME_SCOPE":"system","_GID":"10016","_HOSTNAME":"leios-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_SLICE":"system.slice","_PID":"759","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721"} +{"SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_TRANSPORT":"stdout","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a57;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=88f6c8372a7a8fb9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2647","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.163016385Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionCleanup\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@3\"},\"kind\":\"ConnectionCleanup\"},\"sev\":\"Debug\",\"thread\":\"100\",\"host\":\"leios-node\"}","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__REALTIME_TIMESTAMP":"1761317026185578","_RUNTIME_SCOPE":"system","__MONOTONIC_TIMESTAMP":"32908705","_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service"} +{"_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2648","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.163086505Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":0,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"100\",\"host\":\"leios-node\"}","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a58;b=082ebd52b7694299b9566558b64d809c;m=1f625a1;t=641e893aec16a;x=11898d32f36777dd","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_COMM":"cardano-node","_UID":"10016","SYSLOG_FACILITY":"3","_GID":"10016","__MONOTONIC_TIMESTAMP":"32908705","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317026185578","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_HOSTNAME":"leios-node","_TRANSPORT":"stdout","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_RUNTIME_SCOPE":"system","__SEQNUM":"2649","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.198557494Z\",\"ns\":\"Net.PeerSelection.Selection.BigLedgerPeersResults\",\"data\":{\"diffTime\":8,\"group\":3,\"kind\":\"BigLedgerPeersResults\",\"result\":[]},\"sev\":\"Info\",\"thread\":\"54\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_FACILITY":"3","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a59;b=082ebd52b7694299b9566558b64d809c;m=1f6910b;t=641e893af2cd5;x=a2b89c9e90d25070","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026213077","_TRANSPORT":"stdout","_UID":"10016","_PID":"759","__MONOTONIC_TIMESTAMP":"32936203"} +{"_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_GID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5a;b=082ebd52b7694299b9566558b64d809c;m=1f768ea;t=641e893b004af;x=75470ab75ad0ca69","_PID":"759","__MONOTONIC_TIMESTAMP":"32991466","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.267794227Z\",\"ns\":\"Net.Server.Local.AcceptConnection\",\"data\":{\"address\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"AcceptConnection\"},\"sev\":\"Debug\",\"thread\":\"48\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","PRIORITY":"6","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317026268335","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","__SEQNUM":"2650"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317026268335","_COMM":"cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5b;b=082ebd52b7694299b9566558b64d809c;m=1f768ea;t=641e893b004af;x=41a2b3a470bf2fe5","_PID":"759","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.267927204Z\",\"ns\":\"Net.ConnectionManager.Local.IncludeConnection\",\"data\":{\"kind\":\"IncludeConnection\",\"provenance\":\"Inbound\",\"remoteAddress\":{\"path\":\"/run/cardano-node/node.socket@4\"}},\"sev\":\"Debug\",\"thread\":\"106\",\"host\":\"leios-node\"}","__SEQNUM":"2651","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_RUNTIME_SCOPE":"system","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CAP_EFFECTIVE":"0","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"32991466","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016"} +{"PRIORITY":"6","_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__REALTIME_TIMESTAMP":"1761317026268335","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.268190087Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":0}},\"sev\":\"Debug\",\"thread\":\"106\",\"host\":\"leios-node\"}","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"32991466","_CAP_EFFECTIVE":"0","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_COMM":"cardano-node","__SEQNUM":"2652","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5c;b=082ebd52b7694299b9566558b64d809c;m=1f768ea;t=641e893b004af;x=bbbb6e40395f3241","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"_SYSTEMD_UNIT":"cardano-node.service","_RUNTIME_SCOPE":"system","_PID":"759","__REALTIME_TIMESTAMP":"1761317026286133","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_FACILITY":"3","_GID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__MONOTONIC_TIMESTAMP":"33009262","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_HOSTNAME":"leios-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5d;b=082ebd52b7694299b9566558b64d809c;m=1f7ae6e;t=641e893b04a35;x=41bf648d69eed6a0","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","PRIORITY":"6","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__SEQNUM":"2653","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.279020514Z\",\"ns\":\"Net.Handshake.Local.Receive.ProposeVersions\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@4\\\"}\",\"event\":\"Recv AnyMessage MsgProposeVersions (fromList [(NodeToClientV_16,TList [TInt 42,TBool False]),(NodeToClientV_17,TList [TInt 42,TBool False]),(NodeToClientV_18,TList [TInt 42,TBool False]),(NodeToClientV_19,TList [TInt 42,TBool False]),(NodeToClientV_20,TList [TInt 42,TBool False])])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"107\",\"host\":\"leios-node\"}","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__REALTIME_TIMESTAMP":"1761317026286133","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__MONOTONIC_TIMESTAMP":"33009262","_UID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.279148184Z\",\"ns\":\"Net.Handshake.Local.Send.AcceptVersion\",\"data\":{\"bearer\":\"ConnectionId {localAddress = LocalAddress \\\"/run/cardano-node/node.socket\\\", remoteAddress = LocalAddress \\\"/run/cardano-node/node.socket@4\\\"}\",\"event\":\"Send AnyMessage MsgAcceptVersion NodeToClientV_20 (TList [TInt 42,TBool False])\",\"kind\":\"HandshakeTrace\"},\"sev\":\"Info\",\"thread\":\"107\",\"host\":\"leios-node\"}","_GID":"10016","_SYSTEMD_SLICE":"system.slice","_PID":"759","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5e;b=082ebd52b7694299b9566558b64d809c;m=1f7ae6e;t=641e893b04a35;x=5e8811c0d23bd950","SYSLOG_IDENTIFIER":"cardano-node-start","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","__SEQNUM":"2654","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","_COMM":"cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_UID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026286133","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_TRANSPORT":"stdout","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.279180869Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionHandler\",\"data\":{\"connectionHandler\":{\"agreedOptions\":{\"networkMagic\":42,\"query\":false},\"kind\":\"HandshakeSuccess\",\"versionNumber\":20},\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"ConnectionHandler\"},\"sev\":\"Info\",\"thread\":\"107\",\"host\":\"leios-node\"}","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a5f;b=082ebd52b7694299b9566558b64d809c;m=1f7ae6e;t=641e893b04a35;x=101f8bd1683fd8ca","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_GID":"10016","_HOSTNAME":"leios-node","__SEQNUM":"2655","__MONOTONIC_TIMESTAMP":"33009262","PRIORITY":"6","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} +{"_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"33031558","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_CAP_EFFECTIVE":"0","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.295272579Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"106\",\"host\":\"leios-node\"}","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317026308432","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a60;b=082ebd52b7694299b9566558b64d809c;m=1f80586;t=641e893b0a150;x=2e70d08eecce45f8","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM":"2656"} +{"__REALTIME_TIMESTAMP":"1761317026308432","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.301400733Z\",\"ns\":\"Net.InboundGovernor.Local.NewConnection\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"NewConnection\",\"provenance\":\"Inbound\"},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__MONOTONIC_TIMESTAMP":"33031558","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a61;b=082ebd52b7694299b9566558b64d809c;m=1f80586;t=641e893b0a150;x=c54fa9e03a6ead3a","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__SEQNUM":"2657","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","_GID":"10016","_RUNTIME_SCOPE":"system","_UID":"10016","_PID":"759","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"__MONOTONIC_TIMESTAMP":"33031558","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a62;b=082ebd52b7694299b9566558b64d809c;m=1f80586;t=641e893b0a150;x=5dec9fbbc0c50df","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_CAP_EFFECTIVE":"0","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.30145884Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","_COMM":"cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","__REALTIME_TIMESTAMP":"1761317026308432","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__SEQNUM":"2658","_UID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","_SYSTEMD_SLICE":"system.slice"} +{"__REALTIME_TIMESTAMP":"1761317026308432","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a63;b=082ebd52b7694299b9566558b64d809c;m=1f80586;t=641e893b0a150;x=4ddc3945840408bd","__SEQNUM":"2659","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.301479793Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"33031558","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_RUNTIME_SCOPE":"system","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4"} +{"PRIORITY":"6","SYSLOG_FACILITY":"3","_UID":"10016","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2660","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a64;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=54c51771f2cdf6be","_SYSTEMD_UNIT":"cardano-node.service","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312238143Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"33049891","_TRANSPORT":"stdout","_CAP_EFFECTIVE":"0","__REALTIME_TIMESTAMP":"1761317026326763","_GID":"10016","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__SEQNUM":"2661","_TRANSPORT":"stdout","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312260493Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToWarmRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"PromotedToWarmRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundIdleSt\"}}},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__MONOTONIC_TIMESTAMP":"33049891","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a65;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=84e75e52d6dcb59a","__REALTIME_TIMESTAMP":"1761317026326763","_COMM":"cardano-node","_UID":"10016","PRIORITY":"6","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_HOSTNAME":"leios-node","_CAP_EFFECTIVE":"0","SYSLOG_FACILITY":"3"} +{"_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","__SEQNUM":"2662","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","SYSLOG_IDENTIFIER":"cardano-node-start","__MONOTONIC_TIMESTAMP":"33049891","_RUNTIME_SCOPE":"system","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a66;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=1a5b39ba5fb2a487","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312279489Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":1},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317026326763","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_CAP_EFFECTIVE":"0","_UID":"10016"} +{"__REALTIME_TIMESTAMP":"1761317026326763","SYSLOG_FACILITY":"3","_TRANSPORT":"stdout","_SYSTEMD_SLICE":"system.slice","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_COMM":"cardano-node","_UID":"10016","_CAP_EFFECTIVE":"0","_RUNTIME_SCOPE":"system","__SEQNUM":"2663","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"33049891","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312298766Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"RemoteWarmSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_PID":"759","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a67;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=f0d58b4c08bbabc2","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","SYSLOG_FACILITY":"3","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_HOSTNAME":"leios-node","__SEQNUM":"2664","__REALTIME_TIMESTAMP":"1761317026326763","_GID":"10016","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312347375Z\",\"ns\":\"Net.InboundGovernor.Local.PromotedToHotRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"PromotedToHotRemote\"},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a68;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=51f7429c8b396720","_TRANSPORT":"stdout","__MONOTONIC_TIMESTAMP":"33049891","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_CAP_EFFECTIVE":"0","PRIORITY":"6"} +{"_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","__MONOTONIC_TIMESTAMP":"33049891","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2665","__REALTIME_TIMESTAMP":"1761317026326763","_GID":"10016","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_TRANSPORT":"stdout","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a69;b=082ebd52b7694299b9566558b64d809c;m=1f84d23;t=641e893b0e8eb;x=cf15808ae3f5666","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312362182Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":1,\"idlePeers\":0,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","PRIORITY":"6","_RUNTIME_SCOPE":"system"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6a;b=082ebd52b7694299b9566558b64d809c;m=1f8d769;t=641e893b17331;x=cc7393887940b647","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_GID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","PRIORITY":"6","__SEQNUM":"2666","__MONOTONIC_TIMESTAMP":"33085289","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312374474Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"RemoteHotSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__REALTIME_TIMESTAMP":"1761317026362161","_PID":"759","SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_COMM":"cardano-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_SYSTEMD_SLICE":"system.slice"} +{"_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","PRIORITY":"6","SYSLOG_IDENTIFIER":"cardano-node-start","_UID":"10016","_TRANSPORT":"stdout","__SEQNUM":"2667","__REALTIME_TIMESTAMP":"1761317026362161","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_PID":"759","_SYSTEMD_SLICE":"system.slice","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","__MONOTONIC_TIMESTAMP":"33085289","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6b;b=082ebd52b7694299b9566558b64d809c;m=1f8d769;t=641e893b17331;x=46a08b92c7ecf50a","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.312491248Z\",\"ns\":\"StateQueryServer.Receive.Acquire\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgAcquire\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system"} +{"PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_TRANSPORT":"stdout","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.345736535Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__REALTIME_TIMESTAMP":"1761317026362161","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6c;b=082ebd52b7694299b9566558b64d809c;m=1f8d769;t=641e893b17331;x=c24586a4a09d10cd","_GID":"10016","__SEQNUM":"2668","_PID":"759","__MONOTONIC_TIMESTAMP":"33085289","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_UID":"10016","_BOOT_ID":"082ebd52b7694299b9566558b64d809c"} +{"_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__REALTIME_TIMESTAMP":"1761317026381824","_TRANSPORT":"stdout","_UID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.361568994Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__MONOTONIC_TIMESTAMP":"33104951","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_GID":"10016","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6d;b=082ebd52b7694299b9566558b64d809c;m=1f92437;t=641e893b1c000;x=284f6e06e56fae40","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM":"2669"} +{"_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM":"2670","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_GID":"10016","_RUNTIME_SCOPE":"system","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_HOSTNAME":"leios-node","__MONOTONIC_TIMESTAMP":"33112512","_CAP_EFFECTIVE":"0","_COMM":"cardano-node","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","SYSLOG_FACILITY":"3","__REALTIME_TIMESTAMP":"1761317026389385","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.375411815Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_PID":"759","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6e;b=082ebd52b7694299b9566558b64d809c;m=1f941c0;t=641e893b1dd89;x=5697984a76ac1f95"} +{"SYSLOG_FACILITY":"3","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_HOSTNAME":"leios-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"33118942","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","PRIORITY":"6","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__SEQNUM":"2671","_SYSTEMD_SLICE":"system.slice","_CAP_EFFECTIVE":"0","_GID":"10016","__REALTIME_TIMESTAMP":"1761317026395813","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a6f;b=082ebd52b7694299b9566558b64d809c;m=1f95ade;t=641e893b1f6a5;x=362d9d470d2624d8","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.394474014Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_COMM":"cardano-node","_PID":"759","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_GID":"10016","_CAP_EFFECTIVE":"0","__SEQNUM":"2672","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026402975","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a70;b=082ebd52b7694299b9566558b64d809c;m=1f976d9;t=641e893b2129f;x=f882ae121e8f8e28","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","PRIORITY":"6","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.395690091Z\",\"ns\":\"StateQueryServer.Receive.Query\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgQuery\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_RUNTIME_SCOPE":"system","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"33126105","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_UID":"10016","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__SEQNUM":"2673","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_FACILITY":"3","PRIORITY":"6","_PID":"759","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_COMM":"cardano-node","_CAP_EFFECTIVE":"0","_HOSTNAME":"leios-node","__REALTIME_TIMESTAMP":"1761317026410960","__MONOTONIC_TIMESTAMP":"33134089","_GID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a71;b=082ebd52b7694299b9566558b64d809c;m=1f99609;t=641e893b231d0;x=4ff851f426961e75","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.410057838Z\",\"ns\":\"StateQueryServer.Receive.Release\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingAcquired\",\"kind\":\"MsgRelease\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node"} +{"__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_SLICE":"system.slice","_TRANSPORT":"stdout","_UID":"10016","__MONOTONIC_TIMESTAMP":"33134089","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__REALTIME_TIMESTAMP":"1761317026410960","__SEQNUM":"2674","PRIORITY":"6","_CAP_EFFECTIVE":"0","_PID":"759","_GID":"10016","_COMM":"cardano-node","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a72;b=082ebd52b7694299b9566558b64d809c;m=1f99609;t=641e893b231d0;x=38de56654ccb7dec","_RUNTIME_SCOPE":"system","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_UNIT":"cardano-node.service","_HOSTNAME":"leios-node","SYSLOG_FACILITY":"3","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.4101274Z\",\"ns\":\"StateQueryServer.Receive.Done\",\"data\":{\"kind\":\"Recv\",\"msg\":{\"agency\":\"SingIdle\",\"kind\":\"MsgDone\"},\"peer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"}},\"sev\":\"Info\",\"thread\":\"110\",\"host\":\"leios-node\"}"} +{"_GID":"10016","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","__SEQNUM":"2675","SYSLOG_FACILITY":"3","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_COMM":"cardano-node","_TRANSPORT":"stdout","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_PID":"759","__MONOTONIC_TIMESTAMP":"33144889","PRIORITY":"6","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_CAP_EFFECTIVE":"0","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a73;b=082ebd52b7694299b9566558b64d809c;m=1f9c039;t=641e893b25c03;x=c136491dbf5a9d29","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.421367097Z\",\"ns\":\"Net.Mux.Local.CleanExit\",\"data\":{\"bearer\":{\"connectionId\":\"LocalAddress \\\"/run/cardano-node/node.socket\\\" LocalAddress \\\"/run/cardano-node/node.socket@4\\\"\"},\"event\":{\"kind\":\"Mux.TraceCleanExit\",\"miniProtocolDir\":\"ResponderDir\",\"miniProtocolNum\":\"MiniProtocolNum 7\",\"msg\":\"Miniprotocol terminated cleanly\"},\"kind\":\"Mux.Trace\"},\"sev\":\"Notice\",\"thread\":\"107\",\"host\":\"leios-node\"}","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_SYSTEMD_SLICE":"system.slice","__REALTIME_TIMESTAMP":"1761317026421763","_HOSTNAME":"leios-node"} +{"_UID":"10016","_COMM":"cardano-node","_SYSTEMD_SLICE":"system.slice","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a74;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=4f0a1f9a0d241a37","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.429028685Z\",\"ns\":\"Net.ConnectionManager.Local.ConnectionManagerCounters\",\"data\":{\"kind\":\"ConnectionManagerCounters\",\"state\":{\"duplex\":0,\"fullDuplex\":0,\"inbound\":1,\"outbound\":0,\"unidirectional\":1}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_PID":"759","__REALTIME_TIMESTAMP":"1761317026430749","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"33153882","SYSLOG_IDENTIFIER":"cardano-node-start","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_CAP_EFFECTIVE":"0","_GID":"10016","_SYSTEMD_UNIT":"cardano-node.service","_TRANSPORT":"stdout","PRIORITY":"6","__SEQNUM":"2676","_HOSTNAME":"leios-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","SYSLOG_FACILITY":"3","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS"} +{"_SYSTEMD_UNIT":"cardano-node.service","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_CAP_EFFECTIVE":"0","__SEQNUM":"2677","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"33153882","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","PRIORITY":"6","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a75;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=99ed0a4e3e468db7","__REALTIME_TIMESTAMP":"1761317026430749","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_GID":"10016","_COMM":"cardano-node","_UID":"10016","_HOSTNAME":"leios-node","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.42907059Z\",\"ns\":\"Net.InboundGovernor.Local.WaitIdleRemote\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"WaitIdleRemote\",\"result\":{\"kind\":\"OperationSuccess\",\"operationSuccess\":{\"dataFlow\":\"Unidirectional\",\"kind\":\"InboundSt\"}}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_TRANSPORT":"stdout"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM":"2678","PRIORITY":"6","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026430749","_UID":"10016","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"33153882","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_COMM":"cardano-node","SYSLOG_FACILITY":"3","_RUNTIME_SCOPE":"system","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a76;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=aab0b98c05ae09bc","_PID":"759","_HOSTNAME":"leios-node","_SYSTEMD_UNIT":"cardano-node.service","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.429099365Z\",\"ns\":\"Net.InboundGovernor.Local.InboundGovernorCounters\",\"data\":{\"coldPeers\":0,\"hotPeers\":0,\"idlePeers\":1,\"kind\":\"InboundGovernorCounters\",\"warmPeers\":0},\"sev\":\"Info\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","SYSLOG_IDENTIFIER":"cardano-node-start","_TRANSPORT":"stdout","_GID":"10016"} +{"_TRANSPORT":"stdout","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_COMM":"cardano-node","SYSLOG_IDENTIFIER":"cardano-node-start","_RUNTIME_SCOPE":"system","_SYSTEMD_SLICE":"system.slice","_SYSTEMD_UNIT":"cardano-node.service","__MONOTONIC_TIMESTAMP":"33153882","_CAP_EFFECTIVE":"0","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.429130933Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_PID":"759","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__REALTIME_TIMESTAMP":"1761317026430749","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a77;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=33e18ad4b66e9d7d","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","PRIORITY":"6","_GID":"10016","SYSLOG_FACILITY":"3","__SEQNUM":"2679"} +{"__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a78;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=3425371f1165daa0","_RUNTIME_SCOPE":"system","__SEQNUM":"2680","__REALTIME_TIMESTAMP":"1761317026430749","_UID":"10016","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","_TRANSPORT":"stdout","_PID":"759","SYSLOG_IDENTIFIER":"cardano-node-start","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","_GID":"10016","_CAP_EFFECTIVE":"0","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","PRIORITY":"6","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.429197422Z\",\"ns\":\"Net.InboundGovernor.Local.ResponderRestarted\",\"data\":{\"connectionId\":{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"kind\":\"ResponderStarted\",\"miniProtocolNum\":{\"kind\":\"MiniProtocolNum\",\"num\":7}},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","_SYSTEMD_SLICE":"system.slice","_COMM":"cardano-node","_HOSTNAME":"leios-node","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","__MONOTONIC_TIMESTAMP":"33153882"} +{"_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_SYSTEMD_UNIT":"cardano-node.service","_UID":"10016","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_RUNTIME_SCOPE":"system","SYSLOG_FACILITY":"3","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service","SYSLOG_IDENTIFIER":"cardano-node-start","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","__REALTIME_TIMESTAMP":"1761317026430749","_TRANSPORT":"stdout","_PID":"759","__SEQNUM":"2681","_HOSTNAME":"leios-node","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","__MONOTONIC_TIMESTAMP":"33153882","_CAP_EFFECTIVE":"0","_SYSTEMD_SLICE":"system.slice","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.429222006Z\",\"ns\":\"Net.InboundGovernor.Local.RemoteState\",\"data\":{\"kind\":\"RemoteState\",\"remoteSt\":[[{\"localAddress\":\"/run/cardano-node/node.socket\",\"remoteAddress\":\"/run/cardano-node/node.socket@4\"},\"RemoteIdleSt\"]]},\"sev\":\"Debug\",\"thread\":\"42\",\"host\":\"leios-node\"}","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a79;b=082ebd52b7694299b9566558b64d809c;m=1f9e35a;t=641e893b27f1d;x=a962a8f7f4cd5525","_COMM":"cardano-node","_GID":"10016","PRIORITY":"6"} +{"_EXE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node","_TRANSPORT":"stdout","_RUNTIME_SCOPE":"system","_SYSTEMD_UNIT":"cardano-node.service","__CURSOR":"s=b0f1f59ccdcb4f0392143208fae505e9;i=a7a;b=082ebd52b7694299b9566558b64d809c;m=2003e84;t=641e893b8da4a;x=1b980a47644d41f2","_MACHINE_ID":"3dec785fe9464e699990a3a4818a033c","SYSLOG_FACILITY":"3","MESSAGE":"{\"at\":\"2025-10-24T14:43:46.847123164Z\",\"ns\":\"Resources\",\"data\":{\"Alloc\":349656856,\"CentiBlkIO\":0,\"CentiCpu\":130,\"CentiGC\":2,\"CentiMut\":121,\"FsRd\":50929664,\"FsWr\":409600,\"GcsMajor\":2,\"GcsMinor\":9,\"Heap\":49283072,\"Live\":5234816,\"NetRd\":0,\"NetWr\":0,\"RSS\":100007936,\"Threads\":12,\"kind\":\"ResourceStats\"},\"sev\":\"Info\",\"thread\":\"11\",\"host\":\"leios-node\"}","_SYSTEMD_INVOCATION_ID":"dc1e985e735d4ab8ac6587c0a322b5a4","_SYSTEMD_SLICE":"system.slice","_BOOT_ID":"082ebd52b7694299b9566558b64d809c","PRIORITY":"6","_COMM":"cardano-node","_STREAM_ID":"51814cf187894dfab5b582cf6bb69721","_GID":"10016","SYSLOG_IDENTIFIER":"cardano-node-start","_PID":"759","_CAP_EFFECTIVE":"0","__SEQNUM":"2682","__REALTIME_TIMESTAMP":"1761317026847306","_HOSTNAME":"leios-node","__SEQNUM_ID":"b0f1f59ccdcb4f0392143208fae505e9","_UID":"10016","__MONOTONIC_TIMESTAMP":"33570436","_CMDLINE":"/nix/store/241xnb7lfq9axwiw3ric0qsxxq3z3a9r-cardano-node-exe-cardano-node-10.5.1/bin/cardano-node run --config /etc/cardano-node/config.json --database-path /var/lib/cardano-node/db-preview --topology /etc/cardano-node/topology.json --host-addr 0.0.0.0 --port 3001 --socket-path /run/cardano-node/node.socket --signing-key /etc/cardano-node/byron-delegate.key --delegation-certificate /etc/cardano-node/byron-delegation.cert --shelley-vrf-key /etc/cardano-node/vrf.skey --shelley-kes-key /etc/cardano-node/kes.skey --shelley-operational-certificate /etc/cardano-node/opcert.cert +RTS -N2 -I0 -A16m -qg -qb --disable-delayed-os-memory-return -RTS","_SYSTEMD_CGROUP":"/system.slice/cardano-node.service"} diff --git a/scripts/leios-demo/demo_analysis.ipynb b/scripts/leios-demo/demo_analysis.ipynb index 0fdbb7a6fd..ba980a76a4 100644 --- a/scripts/leios-demo/demo_analysis.ipynb +++ b/scripts/leios-demo/demo_analysis.ipynb @@ -12,23 +12,14 @@ "cell_type": "code", "execution_count": null, "id": "34d6fcb0-7a19-4bcd-940f-4553a53b2334", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, + "metadata": {}, "outputs": [], "source": [ "import json\n", "import pandas as pd\n", "import altair as alt\n", - "import itables as itables\n", - "import ipywidgets as widgets\n", - "import plotly.offline as plotly\n", "import plotly.express as px\n", - "\n", - "plotly.init_notebook_mode(connected=True) \n", - "itables.init_notebook_mode(all_interactive=True)" + "from jupyter_utils import *" ] }, { @@ -43,50 +34,16 @@ "cell_type": "code", "execution_count": null, "id": "fb9e23cd-9257-40a4-bd56-2e76797294a5", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, + "metadata": {}, "outputs": [], "source": [ "# cardano_node_0_df, cardano_node_0_df and all_df\n", - "def df_from_cardano_node_logs(fp):\n", - " lines = open(fp, \"r\").readlines()\n", - " at_lines = [ json.loads(line) for line in lines if line.startswith('{\"at') ]\n", - " return pd.DataFrame.from_records(at_lines)\n", - "\n", - "\n", - "def events_chart(df, y, color):\n", - " fig = px.scatter(\n", - " df, \n", - " x='at', \n", - " y=y, \n", - " color=color, # Optional: Group events by color\n", - " title='Event chart',\n", - " hover_data=['data'] # Show event name on hover\n", - " )\n", - "\n", - " # Add the Range Slider and Range Selector Buttons\n", - " fig.update_xaxes(\n", - " # Enable the Range Slider below the chart\n", - " rangeslider_visible=True,\n", - " \n", - " # Add preset buttons for easy selection (e.g., 1 month, 6 months)\n", - " rangeselector=dict(\n", - " buttons=list([\n", - " dict(count=1, label=\"1M\", step=\"month\", stepmode=\"backward\"),\n", - " dict(count=6, label=\"6M\", step=\"month\", stepmode=\"backward\"),\n", - " dict(step=\"all\", label=\"ALL\")\n", - " ])\n", - " )\n", - " )\n", - " return fig\n", "\n", "cardano_node_0_df = df_from_cardano_node_logs(\"data/cardano-node-0.log\")\n", "cardano_node_1_df = df_from_cardano_node_logs(\"data/cardano-node-1.log\")\n", "\n", - "all_df = pd.concat([cardano_node_0_df.assign(source=\"cardano-node-0\"), cardano_node_1_df.assign(source=\"cardano-node-1\")])\n", + "# all_df = pd.concat([cardano_node_0_df.assign(source=\"cardano-node-0\"), cardano_node_1_df.assign(source=\"cardano-node-1\")])\n", + "all_df = df_from_cardano_node_journal(\"data/cardano-node.logs.json\")\n", "\n", "all_df" ] @@ -105,9 +62,6 @@ "id": "b3a4c630-bec8-433d-9bbd-1c7510ab7606", "metadata": { "editable": true, - "jupyter": { - "source_hidden": true - }, "slideshow": { "slide_type": "" }, @@ -124,27 +78,20 @@ "cell_type": "code", "execution_count": null, "id": "9b14673f-2800-47fa-97e6-44723bacebd5", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, + "metadata": {}, "outputs": [], "source": [ "# SELECT * FROM all_df WHERE sev = 'Error'\n", - "display(events_chart(all_df[all_df.sev == \"Error\"], \"source\", \"ns\"))\n", - "all_df[all_df.sev == \"Error\"]" + "error_df = all_df[all_df.sev == \"Error\"]\n", + "display(events_chart(error_df, \"source\", \"ns\"))\n", + "error_df" ] }, { "cell_type": "code", "execution_count": null, "id": "6fa79265-32db-4834-b54c-e7362fa5ece1", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, + "metadata": {}, "outputs": [], "source": [ "# SELECT DISTINCT_COUNT(ns), ARG_MAX(ns), ARG_MIN(ns), ARG_MAX(sev), ARG_MIN(sev) FROM all_df GROUP BY source \n", @@ -166,16 +113,24 @@ "cell_type": "code", "execution_count": null, "id": "54fdda99-554a-4bc3-8a9e-fb346487f4ed", - "metadata": { - "jupyter": { - "source_hidden": true - } - }, + "metadata": {}, "outputs": [], "source": [ - "block_df = all_df[all_df.data.apply(lambda r: 'block' in r)]\n", + "block_df = all_df[all_df.ns.isin(NS_WITH_BLOCK_HASH) & (~all_df.apply(is_exception, axis=1))]\n", + "\n", + "block_df.loc[:, 'block'] = block_df.apply(lambda r: extract_block_hash(r)[:10], axis=1)\n", "\n", - "events_chart(block_df, \"source\", \"ns\")" + "block_df" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "id": "bc51e1c8-bd41-4bc9-af82-56eb46c21fe8", + "metadata": {}, + "outputs": [], + "source": [ + "events_chart(block_df, \"block\", \"source\")" ] } ], diff --git a/scripts/leios-demo/jupyter_utils.py b/scripts/leios-demo/jupyter_utils.py new file mode 100644 index 0000000000..6b27c7a776 --- /dev/null +++ b/scripts/leios-demo/jupyter_utils.py @@ -0,0 +1,119 @@ +# Utility module for analysis in Jupyter notebooks +import json +import pandas as pd +import altair as alt +import itables as itables +import ipywidgets as widgets +import plotly.offline as plotly +import plotly.express as px + +plotly.init_notebook_mode(connected=True) +itables.init_notebook_mode(all_interactive=True) + + +def df_from_cardano_node_logs(fp): + lines = open(fp, "r").readlines() + at_lines = [json.loads(line) for line in lines if line.startswith('{"at')] + return pd.DataFrame.from_records(at_lines) + + +def df_from_cardano_node_journal(fp): + lines = open(fp, "r").readlines() + records = [] + for line in lines: + js = json.loads(line) + if ( + js["_SYSTEMD_UNIT"] == "cardano-node.service" + and js["MESSAGE"] + and 'at":' in js["MESSAGE"] + ): + records.append(json.loads(js["MESSAGE"])) + df = pd.DataFrame.from_records(records) + return df.assign(source=lambda r: r.host) + + +def events_chart(df, y, color, symbol=None): + fig = px.scatter( + df, + x="at", + y=y, + color=color, # Optional: Group events by color + symbol=color if not symbol else symbol, + title="Event chart", + hover_data=["ns"], # Show event name on hover + ) + + # Add the Range Slider and Range Selector Buttons + fig.update_xaxes( + # Enable the Range Slider below the chart + rangeslider_visible=True, + # Add preset buttons for easy selection (e.g., 1 month, 6 months) + rangeselector=dict( + buttons=list( + [ + dict(count=1, label="1M", step="month", stepmode="backward"), + dict(count=6, label="6M", step="month", stepmode="backward"), + dict(step="all", label="ALL"), + ] + ) + ), + ) + return fig + + +NS_WITH_BLOCK_HASH = [ + "BlockFetch.Client.CompletedBlockFetch", + "BlockFetch.Client.SendFetchRequest", + "ChainDB.AddBlockEvent.AddedBlockToQueue", + "ChainDB.AddBlockEvent.AddedBlockToVolatileDB", + "ChainDB.AddBlockEvent.AddedToCurrentChain", + "ChainDB.AddBlockEvent.ChangingSelection", + "ChainDB.AddBlockEvent.PipeliningEvent.OutdatedTentativeHeader", + "ChainDB.AddBlockEvent.PipeliningEvent.SetTentativeHeader", + "ChainDB.AddBlockEvent.PoppedBlockFromQueue", + "ChainDB.AddBlockEvent.TryAddToCurrentChain", + "ChainDB.ChainSelStarvationEvent", + "ChainSync.Client.DownloadedHeader", + "ChainSync.Client.GaveLoPToken", + "ChainSync.Client.RolledBack", + "ChainSync.Client.ValidatedHeader", + "Consensus.GSM.EnterCaughtUp", + "Consensus.GSM.LeaveCaughtUp", +] + + +def is_exception(record): + return any( + [ + record.ns == "ChainDB.AddBlockEvent.PoppedBlockFromQueue" + and "risingEdge" in record.data, + record.ns == "ChainDB.ChainSelStarvationEvent" + and "risingEdge" in record.data, + record.ns == "ChainSync.Client.RolledBack" + and record.data["tip"]["kind"] == "GenesisPoint", + record.ns == "Consensus.GSM.EnterCaughtUp" + and record.data["currentSelection"]["kind"] == "TipGenesis", + ] + ) + + +def extract_block_hash(record): + if "block" in record.data: + if isinstance(record.data["block"], str): + return record.data["block"] + if "hash" in record.data["block"]: + return record.data["block"]["hash"] + if "headerHash" in record.data["block"]: + return record.data["block"]["headerHash"] + if "headerHash" in record.data: + return record.data["headerHash"] + if "head" in record.data: + return record.data["head"] + if "fallingEdge" in record.data: + return record.data["fallingEdge"]["hash"] + if "newtip" in record.data: + return record.data["newtip"] + if "tip" in record.data: + return record.data["tip"]["headerHash"] + if "currentSelection" in record.data: + return record.data["currentSelection"]["tipHash"] From 97784e7b3ad331874382a0e244e0ee2142f8d6c3 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 12:41:23 -0700 Subject: [PATCH 059/119] leiosdemo202510: added generalized LeiosNotify peers to ouroboros-consensus-diffusion --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 123 +++++++++++++--- .../Ouroboros/Consensus/Node.hs | 2 + .../LeiosDemoOnlyTestNotify.hs | 135 +++++++++++++++++- .../Ouroboros/Consensus/Block/RealPoint.hs | 5 + .../Ouroboros/Consensus/Util/Orphans.hs | 7 + 5 files changed, 252 insertions(+), 20 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index a3beebcff2..460c9c1bcd 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} @@ -51,6 +53,7 @@ import Control.ResourceRegistry import Control.Tracer import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as BSL +import Data.Functor ((<&>)) import Data.Hashable (Hashable) import Data.Int (Int64) import Data.Map.Strict (Map) @@ -128,8 +131,8 @@ import Ouroboros.Network.TxSubmission.Outbound import qualified Ouroboros.Network.Mux as ON -import LeiosDemoOnlyTestFetch (leiosFetchMiniProtocolNum) -import LeiosDemoOnlyTestNotify (leiosNotifyMiniProtocolNum) +import LeiosDemoOnlyTestFetch +import LeiosDemoOnlyTestNotify {------------------------------------------------------------------------------- Handlers @@ -203,6 +206,17 @@ data Handlers m addr blk = Handlers { :: NodeToNodeVersion -> ConnectionId addr -> PeerSharingServer addr m + + , hLeiosNotifyClient + :: NodeToNodeVersion + -> ControlMessageSTM m + -> ConnectionId addr + -> LeiosNotifyClientPeerPipelined (RealPoint blk) () m () + + , hLeiosNotifyServer + :: NodeToNodeVersion + -> ConnectionId addr + -> LeiosNotifyServerPeer (RealPoint blk) () m () } mkHandlers :: @@ -268,6 +282,19 @@ mkHandlers , hKeepAliveServer = \_version _peer -> keepAliveServer , hPeerSharingClient = \_version controlMessageSTM _peer -> peerSharingClient controlMessageSTM , hPeerSharingServer = \_version _peer -> peerSharingServer getPeerSharingAPI + , hLeiosNotifyClient = \_version controlMessageSTM _peer -> + leiosNotifyClientPeerPipelined + (atomically controlMessageSTM <&> \case + Terminate -> Left () + _ -> Right 300 {- TODO magic number -}) + (\case + MsgLeiosBlockAnnouncement{} -> pure () -- TODO + MsgLeiosBlockOffer{} -> pure () -- TODO + MsgLeiosBlockTxsOffer{} -> pure () -- TODO + ) + , hLeiosNotifyServer = \_version _peer -> + leiosNotifyServerPeer + (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO } {------------------------------------------------------------------------------- @@ -275,7 +302,7 @@ mkHandlers -------------------------------------------------------------------------------} -- | Node-to-node protocol codecs needed to run 'Handlers'. -data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS = Codecs { +data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS bLN = Codecs { cChainSyncCodec :: Codec (ChainSync (Header blk) (Point blk) (Tip blk)) e m bCS , cChainSyncCodecSerialised :: Codec (ChainSync (SerialisedHeader blk) (Point blk) (Tip blk)) e m bSCS , cBlockFetchCodec :: Codec (BlockFetch blk (Point blk)) e m bBF @@ -283,6 +310,7 @@ data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS = Codecs { , cTxSubmission2Codec :: Codec (TxSubmission2 (GenTxId blk) (GenTx blk)) e m bTX , cKeepAliveCodec :: Codec KeepAlive e m bKA , cPeerSharingCodec :: Codec (PeerSharing addr) e m bPS + , cLeiosNotifyCodec :: Codec (LeiosNotify (RealPoint blk) ()) e m bLN } -- | Protocol codecs for the node-to-node protocols @@ -296,7 +324,7 @@ defaultCodecs :: forall m blk addr. -> (NodeToNodeVersion -> forall s . CBOR.Decoder s addr) -> NodeToNodeVersion -> Codecs blk addr DeserialiseFailure m - ByteString ByteString ByteString ByteString ByteString ByteString ByteString + ByteString ByteString ByteString ByteString ByteString ByteString ByteString ByteString defaultCodecs ccfg version encAddr decAddr nodeToNodeVersion = Codecs { cChainSyncCodec = codecChainSync @@ -340,6 +368,13 @@ defaultCodecs ccfg version encAddr decAddr nodeToNodeVersion = Codecs { , cKeepAliveCodec = codecKeepAlive_v2 , cPeerSharingCodec = codecPeerSharing (encAddr nodeToNodeVersion) (decAddr nodeToNodeVersion) + + , cLeiosNotifyCodec = + codecLeiosNotify + (encodeRealPoint (encodeRawHash p)) + (decodeRealPoint (decodeRawHash p)) + (\() -> CBOR.encodeNull) + CBOR.decodeNull } where p :: Proxy blk @@ -361,6 +396,7 @@ identityCodecs :: Monad m (AnyMessage (TxSubmission2 (GenTxId blk) (GenTx blk))) (AnyMessage KeepAlive) (AnyMessage (PeerSharing addr)) + (AnyMessage (LeiosNotify (RealPoint blk) ())) identityCodecs = Codecs { cChainSyncCodec = codecChainSyncId , cChainSyncCodecSerialised = codecChainSyncId @@ -369,6 +405,7 @@ identityCodecs = Codecs { , cTxSubmission2Codec = codecTxSubmission2Id , cKeepAliveCodec = codecKeepAliveId , cPeerSharingCodec = codecPeerSharingId + , cLeiosNotifyCodec = codecLeiosNotifyId } {------------------------------------------------------------------------------- @@ -387,6 +424,7 @@ data Tracers' peer ntnAddr blk e f = Tracers { , tTxSubmission2Tracer :: f (TraceLabelPeer peer (TraceSendRecv (TxSubmission2 (GenTxId blk) (GenTx blk)))) , tKeepAliveTracer :: f (TraceLabelPeer peer (TraceSendRecv KeepAlive)) , tPeerSharingTracer :: f (TraceLabelPeer peer (TraceSendRecv (PeerSharing ntnAddr))) + , tLeiosNotifyTracer :: f (TraceLabelPeer peer (TraceSendRecv (LeiosNotify (RealPoint blk) ()))) } instance (forall a. Semigroup (f a)) => Semigroup (Tracers' peer ntnAddr blk e f) where @@ -398,6 +436,7 @@ instance (forall a. Semigroup (f a)) => Semigroup (Tracers' peer ntnAddr blk e f , tTxSubmission2Tracer = f tTxSubmission2Tracer , tKeepAliveTracer = f tKeepAliveTracer , tPeerSharingTracer = f tPeerSharingTracer + , tLeiosNotifyTracer = f tLeiosNotifyTracer } where f :: forall a. Semigroup a @@ -415,6 +454,7 @@ nullTracers = Tracers { , tTxSubmission2Tracer = nullTracer , tKeepAliveTracer = nullTracer , tPeerSharingTracer = nullTracer + , tLeiosNotifyTracer = nullTracer } showTracers :: ( Show blk @@ -434,6 +474,7 @@ showTracers tr = Tracers { , tTxSubmission2Tracer = showTracing tr , tKeepAliveTracer = showTracing tr , tPeerSharingTracer = showTracing tr + , tLeiosNotifyTracer = showTracing tr } {------------------------------------------------------------------------------- @@ -456,7 +497,7 @@ type ServerApp m addr bytes a = -- | Applications for the node-to-node protocols -- -- See 'Network.Mux.Types.MuxApplication' -data Apps m addr bCS bBF bTX bKA bPS a b = Apps { +data Apps m addr bCS bBF bTX bKA bPS bLN a b = Apps { -- | Start a chain sync client that communicates with the given upstream -- node. aChainSyncClient :: ClientApp m addr bCS a @@ -489,6 +530,12 @@ data Apps m addr bCS bBF bTX bKA bPS a b = Apps { -- | Start a peer-sharing server. , aPeerSharingServer :: ServerApp m addr bPS b + + -- | Start a LeiosNotify client. + , aLeiosNotifyClient :: ClientApp m addr bLN a + + -- | Start a LeiosNotify server. + , aLeiosNotifyServer :: ServerApp m addr bLN b } @@ -498,7 +545,7 @@ data Apps m addr bCS bBF bTX bKA bPS a b = Apps { -- They don't depend on the instantiation of the protocol parameters (which -- block type is used, etc.), hence the use of 'RankNTypes'. -- -data ByteLimits bCS bBF bTX bKA = ByteLimits { +data ByteLimits bCS bBF bTX bKA bLN = ByteLimits { blChainSync :: forall header point tip. ProtocolSizeLimits (ChainSync header point tip) @@ -518,22 +565,29 @@ data ByteLimits bCS bBF bTX bKA = ByteLimits { KeepAlive bKA + , blLeiosNotify :: forall point announcement. + ProtocolSizeLimits + (LeiosNotify point announcement) + bLN + } -noByteLimits :: ByteLimits bCS bBF bTX bKA +noByteLimits :: ByteLimits bCS bBF bTX bKA bLN noByteLimits = ByteLimits { blChainSync = byteLimitsChainSync (const 0) , blBlockFetch = byteLimitsBlockFetch (const 0) , blTxSubmission2 = byteLimitsTxSubmission2 (const 0) , blKeepAlive = byteLimitsKeepAlive (const 0) + , blLeiosNotify = byteLimitsLeiosNotify (const 0) } -byteLimits :: ByteLimits ByteString ByteString ByteString ByteString +byteLimits :: ByteLimits ByteString ByteString ByteString ByteString ByteString byteLimits = ByteLimits { blChainSync = byteLimitsChainSync size , blBlockFetch = byteLimitsBlockFetch size , blTxSubmission2 = byteLimitsTxSubmission2 size , blKeepAlive = byteLimitsKeepAlive size + , blLeiosNotify = byteLimitsLeiosNotify size } where size :: ByteString -> Word @@ -542,7 +596,7 @@ byteLimits = ByteLimits { -- | Construct the 'NetworkApplication' for the node-to-node protocols mkApps :: - forall m addrNTN addrNTC blk e bCS bBF bTX bKA bPS. + forall m addrNTN addrNTC blk e bCS bBF bTX bKA bPS bLN. ( IOLike m , MonadTimer m , Ord addrNTN @@ -555,14 +609,14 @@ mkApps :: ) => NodeKernel m addrNTN addrNTC blk -- ^ Needed for bracketing only -> Tracers m addrNTN blk e - -> (NodeToNodeVersion -> Codecs blk addrNTN e m bCS bCS bBF bBF bTX bKA bPS) - -> ByteLimits bCS bBF bTX bKA + -> (NodeToNodeVersion -> Codecs blk addrNTN e m bCS bCS bBF bBF bTX bKA bPS bLN) + -> ByteLimits bCS bBF bTX bKA bLN -> m ChainSyncTimeout -> CsClient.ChainSyncLoPBucketConfig -> CsClient.CSJConfig -> ReportPeerMetrics m (ConnectionId addrNTN) -> Handlers m addrNTN blk - -> Apps m addrNTN bCS bBF bTX bKA bPS NodeToNodeInitiatorResult () + -> Apps m addrNTN bCS bBF bTX bKA bPS bLN NodeToNodeInitiatorResult () mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucketConfig csjConfig ReportPeerMetrics {..} Handlers {..} = Apps {..} where @@ -806,6 +860,40 @@ mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucke $ peerSharingServerPeer $ hPeerSharingServer version them + aLeiosNotifyClient + :: NodeToNodeVersion + -> ExpandedInitiatorContext addrNTN m + -> Channel m bLN + -> m (NodeToNodeInitiatorResult, Maybe bLN) + aLeiosNotifyClient version ExpandedInitiatorContext { + eicConnectionId = them, + eicControlMessage = controlMessageSTM + } channel = do + labelThisThread "LeiosNotifyClient" + ((), trailing) <- runPipelinedPeerWithLimits + (TraceLabelPeer them `contramap` tLeiosNotifyTracer) + (cLeiosNotifyCodec (mkCodecs version)) + blLeiosNotify + timeLimitsLeiosNotify + channel + $ hLeiosNotifyClient version controlMessageSTM them + pure (NoInitiatorResult, trailing) + + aLeiosNotifyServer + :: NodeToNodeVersion + -> ResponderContext addrNTN + -> Channel m bLN + -> m ((), Maybe bLN) + aLeiosNotifyServer version ResponderContext { rcConnectionId = them } channel = do + labelThisThread "LeiosNotifyServer" + runPeerWithLimits + (TraceLabelPeer them `contramap` tLeiosNotifyTracer) + (cLeiosNotifyCodec (mkCodecs version)) + blLeiosNotify + timeLimitsLeiosNotify + channel + $ hLeiosNotifyServer version them + {------------------------------------------------------------------------------- Projections from 'Apps' -------------------------------------------------------------------------------} @@ -820,7 +908,7 @@ initiator :: MiniProtocolParameters -> NodeToNodeVersion -> NodeToNodeVersionData - -> Apps m addr b b b b b a c + -> Apps m addr b b b b b b a c -> OuroborosBundleWithExpandedCtx 'Mux.InitiatorMode addr b m a Void initiator miniProtocolParameters version versionData Apps {..} = nodeToNodeProtocols @@ -851,7 +939,8 @@ initiator miniProtocolParameters version versionData Apps {..} = ON.miniProtocolNum = leiosNotifyMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosNotifyProtocolLimits, - ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) + ON.miniProtocolRun = InitiatorProtocolOnly + (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) } , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, @@ -871,7 +960,7 @@ initiatorAndResponder :: MiniProtocolParameters -> NodeToNodeVersion -> NodeToNodeVersionData - -> Apps m addr b b b b b a c + -> Apps m addr b b b b b b a c -> OuroborosBundleWithExpandedCtx 'Mux.InitiatorResponderMode addr b m a c initiatorAndResponder miniProtocolParameters version versionData Apps {..} = nodeToNodeProtocols @@ -907,7 +996,9 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = ON.miniProtocolNum = leiosNotifyMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosNotifyProtocolLimits, - ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) + ON.miniProtocolRun = InitiatorAndResponderProtocol + (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) + (MiniProtocolCb (\responderCtx -> aLeiosNotifyServer version responderCtx)) } , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs index 037425f737..6e1c2de8c8 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs @@ -625,6 +625,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} = ByteString ByteString ByteString + ByteString NodeToNodeInitiatorResult () mkNodeToNodeApps nodeKernelArgs nodeKernel peerMetrics encAddrNTN decAddrNTN version = @@ -664,6 +665,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} = ByteString ByteString ByteString + ByteString NodeToNodeInitiatorResult () ) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index 4339f7b1b1..db401d8807 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} @@ -10,16 +11,24 @@ {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} module LeiosDemoOnlyTestNotify ( LeiosNotify (..) , SingLeiosNotify (..) , Message (..) + -- * , byteLimitsLeiosNotify , timeLimitsLeiosNotify , codecLeiosNotify , codecLeiosNotifyId + -- * + , LeiosNotifyClientPeerPipelined + , LeiosNotifyServerPeer , leiosNotifyMiniProtocolNum + , leiosNotifyClientPeer + , leiosNotifyClientPeerPipelined + , leiosNotifyServerPeer ) where import qualified Codec.CBOR.Decoding as CBOR @@ -28,15 +37,20 @@ import qualified Codec.CBOR.Read as CBOR import Control.DeepSeq (NFData (..)) import Control.Monad.Class.MonadST import Data.ByteString.Lazy (ByteString) +import Data.Functor ((<&>)) import Data.Kind (Type) import Data.Singletons +import Data.Word (Word32) import qualified Network.Mux.Types as Mux import Network.TypedProtocol.Codec.CBOR import Network.TypedProtocol.Core +import Network.TypedProtocol.Peer +-- import Network.TypedProtocol.Peer.Client import Ouroboros.Network.Protocol.Limits import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) import Text.Printf + ----- leiosNotifyMiniProtocolNum :: Mux.MiniProtocolNum @@ -93,6 +107,7 @@ instance Protocol (LeiosNotify point announcement) where -> Message (LeiosNotify point announcement) StBusy StIdle MsgLeiosBlockOffer :: !point + -> !Word32 -- TODO this size should be redundant, determined by the announcement -> Message (LeiosNotify point announcement) StBusy StIdle MsgLeiosBlockTxsOffer :: !point @@ -186,10 +201,11 @@ encodeLeiosNotify encodeP encodeA = encode CBOR.encodeListLen 2 <> CBOR.encodeWord 1 <> encodeA x - MsgLeiosBlockOffer p -> - CBOR.encodeListLen 2 + MsgLeiosBlockOffer p sz -> + CBOR.encodeListLen 3 <> CBOR.encodeWord 2 <> encodeP p + <> CBOR.encodeWord32 sz MsgLeiosBlockTxsOffer p -> CBOR.encodeListLen 2 <> CBOR.encodeWord 3 @@ -225,9 +241,10 @@ decodeLeiosNotify decodeP decodeA = decode (SingBusy, 2, 1) -> do x <- decodeA return $ SomeMessage $ MsgLeiosBlockAnnouncement x - (SingBusy, 2, 2) -> do + (SingBusy, 3, 2) -> do p <- decodeP - return $ SomeMessage $ MsgLeiosBlockOffer p + sz <- CBOR.decodeWord32 + return $ SomeMessage $ MsgLeiosBlockOffer p sz (SingBusy, 2, 3) -> do p <- decodeP return $ SomeMessage $ MsgLeiosBlockTxsOffer p @@ -286,3 +303,113 @@ codecLeiosNotifyId = Codec {encode, decode} notActiveState stok (_, _) -> DecodeFail $ CodecFailure "codecLeiosNotifyId: no matching message" + +----- + +leiosNotifyClientPeer :: + forall m announcement point a. + Monad m + => + m (Maybe a) + -> + (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) + -> + Peer (LeiosNotify point announcement) AsClient NonPipelined StIdle m a +leiosNotifyClientPeer checkDone handler = + go + where + go :: Peer (LeiosNotify point announcement) AsClient NonPipelined StIdle m a + go = Effect $ checkDone <&> \case + Just x -> + Yield ReflClientAgency MsgDone + $ Done ReflNobodyAgency x + Nothing -> + Yield ReflClientAgency MsgLeiosNotificationRequestNext + $ Await ReflServerAgency $ \msg -> case msg of + MsgLeiosBlockAnnouncement{} -> react msg + MsgLeiosBlockOffer{} -> react msg + MsgLeiosBlockTxsOffer{} -> react msg + + react msg = Effect $ fmap (\() -> go) $ handler msg + +-- | Merely an abbrevation local to this module +type X point announcement m a n = + Peer (LeiosNotify point announcement) AsClient (Pipelined n (C m)) StIdle m a + +type LeiosNotifyClientPeerPipelined point announcement m a = + PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a + +newtype C m = MkC (m ()) + +leiosNotifyClientPeerPipelined :: + forall m announcement point a. + Monad m + => + m (Either a Int) + -- ^ either the return value or else the current max pipelining depth + -> + (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) + -> + PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a +leiosNotifyClientPeerPipelined checkDone handler = + PeerPipelined (go Zero) + where + go :: Nat n -> X point announcement m a n + go !n = Effect $ checkDone <&> \case + Left x -> drainThePipe x n + Right maxDepth -> + case n of + Zero -> sendAnother n + Succ m -> + Collect + (if natToInt n >= maxDepth then Nothing else Just $ sendAnother n) + (\(MkC action) -> Effect $ do action; pure $ go m) + + sendAnother :: Nat n -> X point announcement m a n + sendAnother !n = + YieldPipelined + ReflClientAgency + MsgLeiosNotificationRequestNext + receiver + (go $ Succ n) + + receiver :: Receiver (LeiosNotify point announcement) AsClient StBusy StIdle m (C m) + receiver = + ReceiverAwait ReflServerAgency $ \msg -> case msg of + MsgLeiosBlockAnnouncement{} -> ReceiverDone $ MkC $ handler msg + MsgLeiosBlockOffer{} -> ReceiverDone $ MkC $ handler msg + MsgLeiosBlockTxsOffer{} -> ReceiverDone $ MkC $ handler msg + + drainThePipe :: a -> Nat n -> X point announcement m a n + drainThePipe x = \case + Zero -> + Yield ReflClientAgency MsgDone + $ Done ReflNobodyAgency x + Succ m -> + Collect + Nothing + (\(MkC action) -> Effect $ do action; pure $ drainThePipe x m) + +----- + +type LeiosNotifyServerPeer point announcement m a = + Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () + +leiosNotifyServerPeer :: + forall m announcement point a. + Monad m + => + m (Message (LeiosNotify point announcement) StBusy StIdle) + -> + Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () +leiosNotifyServerPeer handler = + go + where + go :: Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () + go = Await ReflClientAgency $ \msg -> case msg of + MsgDone -> Done ReflNobodyAgency () + MsgLeiosNotificationRequestNext -> Effect $ do + msg <- handler + pure + $ Yield ReflServerAgency msg + $ go diff --git a/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/RealPoint.hs b/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/RealPoint.hs index 1c28ab3b52..f8e4dc89c1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/RealPoint.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/RealPoint.hs @@ -34,6 +34,7 @@ import GHC.Generics import NoThunks.Class (NoThunks (..)) import Ouroboros.Consensus.Block.Abstract import Ouroboros.Consensus.Util.Condense +import Ouroboros.Consensus.Util (ShowProxy (..)) {------------------------------------------------------------------------------- Non-genesis point @@ -49,6 +50,10 @@ deriving instance StandardHash blk => Eq (RealPoint blk) deriving instance StandardHash blk => Ord (RealPoint blk) deriving instance StandardHash blk => Show (RealPoint blk) +instance ShowProxy blk + => ShowProxy (RealPoint blk) where + showProxy _ = "RealPoint " ++ showProxy (Proxy :: Proxy blk) + instance (StandardHash blk, Typeable blk) => NoThunks (RealPoint blk) where showTypeOf _ = show $ typeRep (Proxy @(RealPoint blk)) diff --git a/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util/Orphans.hs b/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util/Orphans.hs index 65d65c5c75..963c231b84 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util/Orphans.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util/Orphans.hs @@ -32,6 +32,13 @@ import System.FS.API (SomeHasFS) import System.FS.API.Types (FsPath, Handle) import System.FS.CRC (CRC (CRC)) +{------------------------------------------------------------------------------- + ShowProxy +-------------------------------------------------------------------------------} + +instance ShowProxy () where + showProxy _ = "()" + {------------------------------------------------------------------------------- Serialise -------------------------------------------------------------------------------} From 30f4ce865f228cacc280fd191b7f9f261513e0b9 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 13:48:33 -0300 Subject: [PATCH 060/119] Add arguments for the anchor slot and its corresponding onset --- scripts/leios-demo/log_parser.py | 34 +++++++++++++++++++++++++++----- 1 file changed, 29 insertions(+), 5 deletions(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 4e681858ee..5100587784 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -133,19 +133,43 @@ def create_and_clean_df( if __name__ == "__main__": - if len(sys.argv) != 3: + if len(sys.argv) != 5: print( - "Configuration Error: Please provide the full path to exactly TWO log files.", + "Configuration Error: Please provide initial-slot, initial-time, and two log files.", file=sys.stderr, ) print( - "Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", + "Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", file=sys.stderr, ) sys.exit(1) - log_path_0 = sys.argv[1] - log_path_1 = sys.argv[2] + # --- Argument Parsing --- + try: + initial_slot = int(sys.argv[1]) + # Use pandas to_datetime, as it's already a dependency and robust. + initial_time = pd.to_datetime(sys.argv[2]) + except ValueError: + print( + f"Configuration Error: Could not parse initial-slot '{sys.argv[1]}' as integer or initial-time '{sys.argv[2]}' as a valid timestamp.", + file=sys.stderr, + ) + sys.exit(1) + except Exception as e: + print( + f"Configuration Error: Error processing initial arguments: {e}", + file=sys.stderr, + ) + sys.exit(1) + + log_path_0 = sys.argv[3] + log_path_1 = sys.argv[4] + + print(f"\n--- Initial Configuration ---") + print(f"Initial Slot: {initial_slot}") + print(f"Initial Time: {initial_time}") + print(f"Log File 0: {log_path_0}") + print(f"Log File 1: {log_path_1}") # --- STEP 1: Create Hash-to-Slot Lookup Table (Headers) --- From 384f0fc77b88b545bd4c3f88f297106b37d15780 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 13:59:43 -0300 Subject: [PATCH 061/119] Add support for POSIX timestamps --- scripts/leios-demo/log_parser.py | 30 ++++++++++++++++++++++++++---- 1 file changed, 26 insertions(+), 4 deletions(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 5100587784..2f075e3cca 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -147,17 +147,39 @@ def create_and_clean_df( # --- Argument Parsing --- try: initial_slot = int(sys.argv[1]) - # Use pandas to_datetime, as it's already a dependency and robust. - initial_time = pd.to_datetime(sys.argv[2]) except ValueError: print( - f"Configuration Error: Could not parse initial-slot '{sys.argv[1]}' as integer or initial-time '{sys.argv[2]}' as a valid timestamp.", + f"Configuration Error: Could not parse initial-slot '{sys.argv[1]}' as an integer.", file=sys.stderr, ) sys.exit(1) + + try: + initial_time_str = sys.argv[2] + # Try to parse as a POSIX timestamp (integer string) first + try: + posix_time = int(initial_time_str) + # Convert from POSIX seconds to a UTC datetime object + initial_time = pd.to_datetime(posix_time, unit="s", utc=True) + print( + f"Note: Interpreted initial-time '{initial_time_str}' as POSIX timestamp (UTC)." + ) + except ValueError: + # If not an integer, try to parse as a standard datetime string + initial_time = pd.to_datetime(initial_time_str) + # If the provided string has no timezone, assume UTC for consistency + if initial_time.tzinfo is None: + initial_time = initial_time.tz_localize("UTC") + print( + f"Note: Interpreted initial-time '{initial_time_str}' as datetime string (assuming UTC)." + ) + else: + # If it has a timezone, convert it to UTC for consistency + initial_time = initial_time.tz_convert("UTC") + except Exception as e: print( - f"Configuration Error: Error processing initial arguments: {e}", + f"Configuration Error: Could not parse initial-time '{sys.argv[2]}' as either a POSIX timestamp or a datetime string. Error: {e}", file=sys.stderr, ) sys.exit(1) From 31bffbe43f585a470fbab5ca41562dcc4648b30d Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 14:02:22 -0300 Subject: [PATCH 062/119] Calculate slot onset time for each slot in the logs --- scripts/leios-demo/log_parser.py | 43 +++++++++++++++++++++++++++++++- 1 file changed, 42 insertions(+), 1 deletion(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 2f075e3cca..b204311ecd 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -262,9 +262,50 @@ def create_and_clean_df( df_merged["at_node_1"] - df_merged["at_node_0"] ).dt.total_seconds() * 1000 + # --- STEP 6: Calculate Slot Onset Time --- + print(f"\n--- Calculating Slot Onset Times ---") + print( + f"Using base slot {initial_slot} at {initial_time} (1 slot = 1 second)" + ) + try: + # Calculate the difference in slots (which equals seconds) + # We must ensure 'slot' is numeric, which create_and_clean_df should have done + df_merged["slot_diff_seconds"] = df_merged["slot"] - initial_slot + + # Convert the second difference into a timedelta and add to the initial time + df_merged["slot_onset"] = initial_time + pd.to_timedelta( + df_merged["slot_diff_seconds"], unit="s" + ) + + # Drop the intermediate calculation column + df_merged = df_merged.drop(columns=["slot_diff_seconds"]) + + except Exception as e: + print( + f"Error: Failed to calculate slot onset times. Check data types. Error: {e}", + file=sys.stderr, + ) + # Continue without onset time if calculation fails + pass + print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") print( "Each row represents a unique block seen by both nodes, joined by hash and slot." ) - print(df_merged.head()) + + # Define desired column order, including the new 'slot_onset' + final_columns = [ + "slot", + "hash", + "slot_onset", + "at_node_0", + "at_node_1", + "latency_ms", + ] + + # Filter list to only columns that actually exist in the dataframe + # This prevents an error if 'slot_onset' failed to be created + existing_columns = [col for col in final_columns if col in df_merged.columns] + + print(df_merged[existing_columns].head()) print(f"\nTotal unique block events matched: {len(df_merged)}") From 45c59c7b386cda4163210356a00a0ad5c2826871 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 14:49:09 -0300 Subject: [PATCH 063/119] Pass anchor slot and its onset to the log_parser script --- scripts/leios-demo/leios-october-demo.sh | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index e1bf1880ed..18e61a43eb 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -127,11 +127,12 @@ popd > /dev/null ## TODO: we should find a better way to wait for the nodes to be started # Calculate the POSIX time 60 seconds from now. REF_TIME_FOR_SLOT=$(( $(date +%s) + 60 )) +INITIAL_SLOT=80 IMMDB_CMD_CORE="cabal run immdb-server \ -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --initial-slot 80 \ + --initial-slot $INITIAL_SLOT \ --initial-time $REF_TIME_FOR_SLOT" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -170,7 +171,9 @@ else echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 fi -python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log +python3 scripts/leios-demo/log_parser.py \ + $INITIAL_SLOT $REF_TIME_FOR_SLOT \ + $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log # 2. Deactivate the Python Virtual Environment before exiting deactivate 2>/dev/null || true From 31af74a3aa3f07c310417012004d7fa27cccd163 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 16:44:37 -0300 Subject: [PATCH 064/119] Add a sanity check for the slot onset calculation --- scripts/leios-demo/log_parser.py | 25 +++++++++++++++++++++++-- 1 file changed, 23 insertions(+), 2 deletions(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index b204311ecd..7d7e0ad378 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -288,12 +288,31 @@ def create_and_clean_df( # Continue without onset time if calculation fails pass + # --- STEP 7: Calculate Diffs from Previous Slot --- + print("\n--- Calculating Diffs from Previous Slot ---") + + # Ensure dataframe is sorted by slot to calculate diffs correctly + df_merged = df_merged.sort_values(by="slot").reset_index(drop=True) + + # Calculate difference from the previous slot + df_merged["slot_diff_from_prev"] = df_merged["slot"].diff().fillna(0).astype(int) + + # Calculate difference from the previous slot's onset time (in seconds) + if "slot_onset" in df_merged.columns: + df_merged["onset_diff_from_prev_s"] = ( + df_merged["slot_onset"] + .diff() + .fillna(pd.Timedelta(seconds=0)) + .dt.total_seconds() + ) + else: + print("Warning: 'slot_onset' column not found. Skipping onset diff calculation.") + print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") print( "Each row represents a unique block seen by both nodes, joined by hash and slot." ) - - # Define desired column order, including the new 'slot_onset' + # Define desired column order, including the new 'slot_onset' and diffs final_columns = [ "slot", "hash", @@ -301,6 +320,8 @@ def create_and_clean_df( "at_node_0", "at_node_1", "latency_ms", + "slot_diff_from_prev", + "onset_diff_from_prev_s", ] # Filter list to only columns that actually exist in the dataframe From d42ef8a46c3445d4e751c4cfcb289de077c6d612 Mon Sep 17 00:00:00 2001 From: dnadales Date: Fri, 24 Oct 2025 17:33:04 -0300 Subject: [PATCH 065/119] Make the script generate a scatter plot --- scripts/leios-demo/leios-october-demo.sh | 3 +- scripts/leios-demo/log_parser.py | 80 +++++++++++++++++++++++- 2 files changed, 79 insertions(+), 4 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 18e61a43eb..f13ccbee6c 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -173,7 +173,8 @@ fi python3 scripts/leios-demo/log_parser.py \ $INITIAL_SLOT $REF_TIME_FOR_SLOT \ - $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log + $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ + "scatter_plot.png" # 2. Deactivate the Python Virtual Environment before exiting deactivate 2>/dev/null || true diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 7d7e0ad378..20650c7045 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -3,6 +3,7 @@ import json import pandas as pd import numpy as np +import matplotlib.pyplot as plt # --- Configuration --- # Filter for the event containing the timestamp we want to measure at node 0 and node 1 @@ -132,14 +133,81 @@ def create_and_clean_df( return df +def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): + """ + Generates and displays a scatter plot of slot_onset vs. at_node_1. + If output_file is provided, saves the plot to that file. + """ + print("\n--- Generating Scatter Plot ---") + try: + if "slot_onset" in df.columns and "at_node_1" in df.columns: + # Ensure both columns are datetime objects for plotting + df["slot_onset"] = pd.to_datetime(df["slot_onset"]) + df["at_node_1"] = pd.to_datetime(df["at_node_1"]) + + plt.figure(figsize=(10, 6)) + plt.scatter(df["slot_onset"], df["at_node_1"], alpha=0.5, s=10) + + # Add a y=x reference line + # Find common min/max for a good 1:1 line + all_times = pd.concat([df["slot_onset"], df["at_node_1"]]) + min_time = all_times.min() + max_time = all_times.max() + plt.plot( + [min_time, max_time], + [min_time, max_time], + "r--", + label="1:1 Line (Onset = Arrival)", + ) + + plt.title("Block Arrival Time (Node 1) vs. Slot Onset Time") + plt.xlabel("Slot Onset Time (Calculated)") + plt.ylabel("Block Arrival Time (at_node_1)") + plt.grid(True, linestyle="--", alpha=0.6) + plt.legend() + plt.tight_layout() + + # Rotate x-axis labels for better readability + plt.xticks(rotation=45) + + if output_file: + plt.savefig(output_file, bbox_inches="tight") + print(f"Plot saved to {output_file}") + else: + print("Displaying plot...") + plt.show() + + plt.close(plt.gcf()) # Close the figure to free memory + + else: + print( + "Warning: 'slot_onset' or 'at_node_1' column not found. Skipping plot generation." + ) + + except ImportError: + print( + "\n--- Plotting Skipped ---", + file=sys.stderr, + ) + print( + "To generate the plot, please install matplotlib: pip install matplotlib", + file=sys.stderr, + ) + except Exception as e: + print( + f"Error: Failed to generate plot. Error: {e}", + file=sys.stderr, + ) + + if __name__ == "__main__": - if len(sys.argv) != 5: + if len(sys.argv) < 5 or len(sys.argv) > 6: print( - "Configuration Error: Please provide initial-slot, initial-time, and two log files.", + "Configuration Error: Please provide initial-slot, initial-time, two log files, and optionally an output plot file.", file=sys.stderr, ) print( - "Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log", + "Example Usage: python log_parser.py /path/to/node-0.log /path/to/node-1.log [output_plot.png]", file=sys.stderr, ) sys.exit(1) @@ -186,12 +254,15 @@ def create_and_clean_df( log_path_0 = sys.argv[3] log_path_1 = sys.argv[4] + plot_output_file = sys.argv[5] if len(sys.argv) == 6 else None print(f"\n--- Initial Configuration ---") print(f"Initial Slot: {initial_slot}") print(f"Initial Time: {initial_time}") print(f"Log File 0: {log_path_0}") print(f"Log File 1: {log_path_1}") + if plot_output_file: + print(f"Plot Output File: {plot_output_file}") # --- STEP 1: Create Hash-to-Slot Lookup Table (Headers) --- @@ -308,6 +379,9 @@ def create_and_clean_df( else: print("Warning: 'slot_onset' column not found. Skipping onset diff calculation.") + # --- STEP 8: Generate Scatter Plot --- + plot_onset_vs_arrival(df_merged, plot_output_file) + print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") print( "Each row represents a unique block seen by both nodes, joined by hash and slot." From 29122592122ea965ecd3b5d3f9f6507bd06a38c6 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 15:24:20 -0700 Subject: [PATCH 066/119] WIP --- .../app/immdb-server.hs | 38 ++++++---- .../ouroboros-consensus-cardano.cabal | 3 + .../Cardano/Tools/ImmDBServer/Diffusion.hs | 69 +++++++++++++++++-- .../Tools/ImmDBServer/MiniProtocols.hs | 42 ++++++++--- .../Ouroboros/Consensus/Network/NodeToNode.hs | 17 +++-- 5 files changed, 138 insertions(+), 31 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index c37b057baf..a26486b7d6 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -5,10 +5,14 @@ module Main (main) where +import qualified Data.Aeson as JSON import Cardano.Crypto.Init (cryptoInit) +import Cardano.Slotting.Slot (SlotNo (..)) import qualified Cardano.Tools.DBAnalyser.Block.Cardano as Cardano import Cardano.Tools.DBAnalyser.HasAnalysis (mkProtocolInfo) import qualified Cardano.Tools.ImmDBServer.Diffusion as ImmDBServer +import Data.Time.Clock (DiffTime) +import qualified Data.Time.Clock.POSIX as POSIX import Data.Void (absurd) import Main.Utf8 (withStdTerminalHandles) import Network.Socket (AddrInfo (addrFlags, addrSocketType)) @@ -17,14 +21,12 @@ import Options.Applicative (ParserInfo, execParser, fullDesc, help, helper, info, long, metavar, progDesc, showDefault, strOption, value, auto, option) import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) -import Cardano.Slotting.Slot (SlotNo (..), WithOrigin (At, Origin)) -import qualified Data.Time.Clock.POSIX as POSIX -import Data.Time.Clock (DiffTime) +import System.Exit (die) main :: IO () main = withStdTerminalHandles $ do cryptoInit - Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot} <- execParser optsParser + Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosScheduleFile} <- execParser optsParser let hints = Socket.defaultHints { addrFlags = [Socket.AI_NUMERICHOST], addrSocketType = Socket.Stream} addrInfo <- do @@ -35,27 +37,32 @@ main = withStdTerminalHandles $ do let args = Cardano.CardanoBlockArgs configFile Nothing ProtocolInfo{pInfoConfig} <- mkProtocolInfo args + + leiosSchedule <- JSON.eitherDecodeFileStrict leiosScheduleFile >>= \case + Left err -> die $ "Failed to decode LeiosSchedule: " ++ err + Right x -> pure x + absurd <$> ImmDBServer.run immDBDir (Socket.addrAddress addrInfo) pInfoConfig (mkGetSlotDelay refSlotNr refTimeForRefSlot) + (leiosSchedule :: ImmDBServer.LeiosSchedule) where -- NB we assume for now the slot duration is 1 second. -- -- If we want to this in the actual chain we will need to access -- the information from the configuration file to run the -- Qry.slotToWallclock query. - mkGetSlotDelay :: SlotNo -> POSIX.POSIXTime -> WithOrigin SlotNo -> IO DiffTime + mkGetSlotDelay :: SlotNo -> POSIX.POSIXTime -> Double -> IO DiffTime mkGetSlotDelay refSlotNr refTimeForRefSlot = -- If slot < refSlotNr, we need to subtract to -- refTimeForRefSlot. - let slotToPosix :: SlotNo -> POSIX.POSIXTime - slotToPosix slot = fromIntegral . unSlotNo $ slot -- TODO: here is where we assume the slot duration of 1 second. - in \case Origin -> pure 0 -- TODO: I'm not sure what we want to do here. - At slot -> do - let slotTime = refTimeForRefSlot + (slotToPosix slot - slotToPosix refSlotNr) + let slotToPosix :: Double -> POSIX.POSIXTime + slotToPosix = realToFrac -- TODO: here is where we assume the slot duration of 1 second. + in \slotDbl -> do + let slotTime = refTimeForRefSlot + (slotToPosix slotDbl - slotToPosix (fromIntegral $ unSlotNo refSlotNr)) currentTime <- POSIX.getPOSIXTime - pure $ if currentTime <= slotTime + pure $ if currentTime < slotTime then realToFrac $ slotTime - currentTime else 0 @@ -71,6 +78,8 @@ data Opts = Opts { , refTimeForRefSlot :: POSIX.POSIXTime -- ^ Reference slot onset. Wallclock time that corresponds to the -- reference slot. + , leiosScheduleFile :: FilePath + -- ^ JSON file encoding the 'ImmDBServer.LeiosSchedule' } optsParser :: ParserInfo Opts @@ -112,4 +121,9 @@ optsParser = , help "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)" , metavar "POSIX_SECONDS" ] - pure Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot} + leiosScheduleFile <- strOption $ mconcat + [ long "leios-schedule" + , help "Path to json file specifying when to send Leios offers" + , metavar "PATH" + ] + pure Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosScheduleFile} diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index 90fa6a639b..492f933958 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -568,6 +568,7 @@ library unstable-cardano-tools filepath, fs-api ^>=0.3, githash, + io-classes, microlens, mtl, network, @@ -582,6 +583,7 @@ library unstable-cardano-tools ouroboros-network-framework ^>=0.18, ouroboros-network-protocols, resource-registry, + serialise, singletons, sop-core, sop-extras, @@ -671,6 +673,7 @@ executable immdb-server hs-source-dirs: app main-is: immdb-server.hs build-depends: + aeson, base, cardano-crypto-class, cardano-slotting, diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index a1171e912a..88b93ed778 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -1,16 +1,29 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} -module Cardano.Tools.ImmDBServer.Diffusion (run) where +module Cardano.Tools.ImmDBServer.Diffusion (run, LeiosSchedule (..)) where -import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) +import qualified Data.Aeson as Aeson +import Codec.Serialise (Serialise) +import qualified Codec.Serialise as Serialise +import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, LeiosContext (..)) +import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.ResourceRegistry import Control.Tracer +import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Lazy as BL import Data.Functor.Contravariant ((>$<)) +import qualified Data.Map.Strict as Map +import qualified Data.Text as T +import qualified Data.Text.Encoding as T import Data.Void (Void) +import Data.Word (Word32, Word64) +import GHC.Generics (Generic) import qualified Network.Mux as Mux import Network.Socket (SockAddr (..)) import Ouroboros.Consensus.Block @@ -32,6 +45,7 @@ import Ouroboros.Network.PeerSelection.PeerSharing.Codec (decodeRemoteAddress, encodeRemoteAddress) import qualified Ouroboros.Network.Snocket as Snocket import Ouroboros.Network.Socket (configureSocket) +import System.Exit (die) import System.FS.API (SomeHasFS (..)) import System.FS.API.Types (MountPoint (MountPoint)) import System.FS.IO (ioHasFS) @@ -71,7 +85,8 @@ serve sockAddr application = withIOManager \iocp -> do run :: forall blk. - ( GetPrevHash blk + ( Serialise (HeaderHash blk) + , GetPrevHash blk , ShowProxy blk , SupportedNetworkProtocolVersion blk , SerialiseNodeToNodeConstraints blk @@ -82,9 +97,14 @@ run :: => FilePath -> SockAddr -> TopLevelConfig blk - -> (WithOrigin SlotNo -> IO DiffTime) + -> (Double -> IO DiffTime) + -> LeiosSchedule -> IO Void -run immDBDir sockAddr cfg getSlotDelay = withRegistry \registry -> +run immDBDir sockAddr cfg getSlotDelay leiosSchedule = withRegistry \registry ->do + leiosContext <- do + leiosMailbox <- MVar.newEmptyMVar + pure MkLeiosContext { leiosMailbox } + _threadId <- forkLinkedThread registry "LeiosScheduler" (leiosScheduler getSlotDelay leiosContext leiosSchedule) ImmutableDB.withDB (ImmutableDB.openDB (immDBArgs registry) runWithTempRegistry) \immDB -> serve sockAddr $ immDBServer @@ -93,7 +113,8 @@ run immDBDir sockAddr cfg getSlotDelay = withRegistry \registry -> decodeRemoteAddress immDB networkMagic - getSlotDelay + (getSlotDelay . fromIntegral . unSlotNo) + leiosContext where immDBArgs registry = ImmutableDB.defaultArgs { immCheckIntegrity = nodeCheckIntegrity storageCfg @@ -106,3 +127,39 @@ run immDBDir sockAddr cfg getSlotDelay = withRegistry \registry -> codecCfg = configCodec cfg storageCfg = configStorage cfg networkMagic = getNetworkMagic . configBlock $ cfg + +----- + +data LeiosSchedule = MkLeiosSchedule [(Double, (Word64, T.Text, Maybe Word32))] + deriving (Generic) + +-- | Deriving via "GHC.Generics" +instance Aeson.FromJSON LeiosSchedule + +leiosScheduler :: + Serialise (HeaderHash blk) + => + (Double -> IO DiffTime) + -> + LeiosContext blk IO + -> + LeiosSchedule + -> + IO () +leiosScheduler getSlotDelay leiosContext = + \(MkLeiosSchedule x) -> do + y <- + traverse (traverse cnv . reverse) + $ Map.fromListWith (++) [ (k, [v]) | (k, v) <- x ] + flip mapM_ (Map.toAscList y) $ \(slotDbl, msgs) -> do + getSlotDelay slotDbl >>= threadDelay + mapM_ (MVar.putMVar (leiosMailbox leiosContext)) msgs + where + cnv (ebSlot, ebHashText, !mbEbBytesSize) = do + let bytes = T.encodeUtf8 ebHashText + ebHash <- + case fmap BL.fromStrict (BS16.decode bytes) >>= either (Left . show) Right . Serialise.deserialiseOrFail of + Left err -> die $ "bad hash in Leios schedule! " ++ T.unpack ebHashText ++ " " ++ err + Right y -> pure y + let !rp = RealPoint (fromIntegral ebSlot) ebHash + pure (rp, mbEbBytesSize) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 617fbdd355..2bb8f9458d 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -12,10 +12,15 @@ {-# LANGUAGE TypeApplications #-} -- | Implement ChainSync and BlockFetch servers on top of just the immutable DB. -module Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer) where +module Cardano.Tools.ImmDBServer.MiniProtocols ( + immDBServer, + LeiosContext (..), + ) where +import Cardano.Slotting.Slot (WithOrigin (At)) import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR +import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Monad (forever) import Control.ResourceRegistry import Control.Tracer @@ -24,6 +29,7 @@ import qualified Data.ByteString.Lazy as BL import Data.Functor ((<&>)) import qualified Data.Map.Strict as Map import Data.Typeable (Typeable) +import Data.Word (Word32) import Data.Void (Void) import GHC.Generics (Generic) import qualified Network.Mux as Mux @@ -61,7 +67,7 @@ import Ouroboros.Network.Protocol.Handshake.Version (Version (..)) import Ouroboros.Network.Protocol.KeepAlive.Server (keepAliveServerPeer) -import LeiosDemoOnlyTestFetch +-- import LeiosDemoOnlyTestFetch import LeiosDemoOnlyTestNotify immDBServer :: @@ -77,10 +83,11 @@ immDBServer :: -> (NodeToNodeVersion -> forall s . CBOR.Decoder s addr) -> ImmutableDB m blk -> NetworkMagic - -> (WithOrigin SlotNo -> m DiffTime) + -> (SlotNo -> m DiffTime) + -> LeiosContext blk m -> Versions NodeToNodeVersion NodeToNodeVersionData (OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode addr BL.ByteString m Void ()) -immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay = do +immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do forAllVersions application where forAllVersions :: @@ -132,18 +139,21 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay = do Mux.StartOnDemand leiosNotifyMiniProtocolNum (const Consensus.N2N.leiosNotifyProtocolLimits) - undefined + leiosNotifyProt +{- , mkMiniProtocol Mux.StartOnDemand leiosFetchMiniProtocolNum (const Consensus.N2N.leiosFetchProtocolLimits) undefined +-} ] where Consensus.N2N.Codecs { cKeepAliveCodec , cChainSyncCodecSerialised , cBlockFetchCodecSerialised + , cLeiosNotifyCodec } = Consensus.N2N.defaultCodecs codecCfg blockVersion encAddr decAddr version @@ -166,6 +176,14 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay = do txSubmissionProt = -- never reply, there is no timeout MiniProtocolCb $ \_ctx _channel -> forever $ threadDelay 10 + leiosNotifyProt = + MiniProtocolCb $ \_ctx channel -> + runPeer nullTracer cLeiosNotifyCodec channel + $ leiosNotifyServerPeer + (MVar.takeMVar (leiosMailbox leios) <&> \case + (p, Just sz) -> MsgLeiosBlockOffer p sz + (p, Nothing) -> MsgLeiosBlockTxsOffer p + ) mkMiniProtocol miniProtocolStart miniProtocolNum limits proto = MiniProtocol { miniProtocolNum @@ -187,7 +205,7 @@ chainSyncServer :: forall m blk a. (IOLike m, HasHeader blk) => ImmutableDB m blk -> BlockComponent blk (ChainDB.WithPoint blk a) - -> (WithOrigin SlotNo -> m DiffTime) + -> (SlotNo -> m DiffTime) -> ResourceRegistry m -> ChainSyncServer a (Point blk) (Tip blk) m () chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ do @@ -214,11 +232,13 @@ chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ d ImmutableDB.iteratorNext iterator >>= \case ImmutableDB.IteratorExhausted -> do ImmutableDB.iteratorClose iterator + threadDelay (5 :: DiffTime) throwIO ReachedImmutableTip ImmutableDB.IteratorResult a -> do -- Wait until the slot of the current block has been reached - slotDelay <- getSlotDelay $ pointSlot $ ChainDB.point a - threadDelay slotDelay + case pointSlot $ ChainDB.point a of + Origin -> pure () + At slot -> getSlotDelay slot >>= threadDelay pure $ AddBlock a followerClose = ImmutableDB.iteratorClose =<< readTVarIO varIterator @@ -274,3 +294,9 @@ data ImmDBServerException = | TriedToFetchGenesis deriving stock (Show) deriving anyclass (Exception) + +----- + +data LeiosContext blk m = MkLeiosContext { + leiosMailbox :: MVar.MVar m (RealPoint blk, Maybe Word32) + } diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 460c9c1bcd..b724f57512 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -131,8 +131,9 @@ import Ouroboros.Network.TxSubmission.Outbound import qualified Ouroboros.Network.Mux as ON -import LeiosDemoOnlyTestFetch +-- import LeiosDemoOnlyTestFetch import LeiosDemoOnlyTestNotify +import Debug.Trace (traceM) {------------------------------------------------------------------------------- Handlers @@ -289,8 +290,12 @@ mkHandlers _ -> Right 300 {- TODO magic number -}) (\case MsgLeiosBlockAnnouncement{} -> pure () -- TODO - MsgLeiosBlockOffer{} -> pure () -- TODO - MsgLeiosBlockTxsOffer{} -> pure () -- TODO + MsgLeiosBlockOffer _ sz -> do + traceM $ "MsgLeiosBlockOffer " ++ show sz + pure () -- TODO + MsgLeiosBlockTxsOffer{} -> do + traceM "MsgLeiosBlockTxsOffer" + pure () -- TODO ) , hLeiosNotifyServer = \_version _peer -> leiosNotifyServerPeer @@ -942,12 +947,13 @@ initiator miniProtocolParameters version versionData Apps {..} = ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) } - , ON.MiniProtocol { +{- , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosFetchProtocolLimits, ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) } +-} ] } @@ -1000,12 +1006,13 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) (MiniProtocolCb (\responderCtx -> aLeiosNotifyServer version responderCtx)) } - , ON.MiniProtocol { +{- , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosFetchProtocolLimits, ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) } +-} ] } From 9571dbf669465d9ced67a8174c4845087d2fdee4 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 15:46:45 -0700 Subject: [PATCH 067/119] WIP the script --- scripts/leios-demo/leios-october-demo.sh | 94 ++++++++++++++---------- 1 file changed, 55 insertions(+), 39 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index e1bf1880ed..cb4ae874e3 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -1,21 +1,15 @@ #!/bin/bash -# The first parameter should be the path to the local checkout of -# cardano-node. -# -# The second parameter should be the path to the folder +# The only parameter should be the path to the folder # where the data of a benchmarking cluster run is stored # (CLUSTER_RUN_DATA directory). -# Local checkout path of the cardano-node repository -# Safely remove trailing slash if present -CARDANO_NODE_PATH="${1%/}" - # P&T cluster run data -CLUSTER_RUN_DATA="${2%/}" +# Safely remove trailing slash if present +CLUSTER_RUN_DATA="${1%/}" -if [ "$#" -ne 2 ]; then - echo "Error: Please provide two parameters: and ." >&2 +if [ "$#" -ne 1 ]; then + echo "Error: Please provide one parameter, the path to the cluster run data directory." >&2 exit 1 fi @@ -29,6 +23,26 @@ if [ ! -d "$CLUSTER_RUN_DATA" ]; then exit 1 fi +if [[ -z "${cardano_node}" ]]; then + echo "Error: Please set \${cardano_node} to the path to the cardano-node exe." >&2 + exit 1 +fi + +if [[ -z "${immdb_server}" ]]; then + echo "Error: Please set \${immdb_server} to the path to the immdb-server exe." >&2 + exit 1 +fi + +if [[ -z "${REF_SLOT}" ]]; then + echo "Error: Please set \${REF_SLOT} to the reference slot." >&2 + exit 1 +fi + +if [[ -z "$LEIOS_SCHEDULE_PATH" ]]; then + echo "Error: Please set \${LEIOS_SCHEDULE_PATH} to path to the Leios schedule file." >&2 + exit 1 +fi + TMP_DIR=$(mktemp -d) echo "Using temporary directory for DB and logs: $TMP_DIR" @@ -38,8 +52,8 @@ pushd "$CARDANO_NODE_PATH" > /dev/null ## Run cardano-node (node-0) ## -echo "Creating topology-node-0.json in $(pwd)" -cat << EOF > topology-node-0.json +echo "Creating topology-node-0.json in $(TMP_DIR)" +cat << EOF > "${TMP_DIR}/topology-node-0.json" { "bootstrapPeers": [], "localRoots": [ @@ -61,11 +75,11 @@ EOF mkdir -p "$TMP_DIR/node-0/db" -CARDANO_NODE_CMD="cabal run -- cardano-node run \ +CARDANO_NODE_CMD="${cardano_node} run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --topology topology-node-0.json \ + --topology ${TMP_DIR}/topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ - --socket-path node-0.socket \ + --socket-path $TMP_DIR/node-0.socket \ --host-addr 0.0.0.0 --port 3002" echo "Command: $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" @@ -80,7 +94,7 @@ echo "Cardano node 0 started with PID: $CARDANO_NODE_0_PID" ## Run a second Cardano-node (To be eventually replaced by a mocked downstream node) ## -cat << EOF > topology-node-1.json +cat << EOF > "${TMP_DIR}/topology-node-1.json" { "bootstrapPeers": [], "localRoots": [ @@ -102,11 +116,11 @@ EOF mkdir -p "$TMP_DIR/node-1/db" -MOCKED_PEER_CMD="cabal run -- cardano-node run \ +MOCKED_PEER_CMD="${cardano-node} run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --topology topology-node-1.json \ + --topology ${TMP_DIR}/topology-node-1.json \ --database-path $TMP_DIR/node-1/db \ - --socket-path node-1.socket \ + --socket-path $TMP_DIR/node-1.socket \ --host-addr 0.0.0.0 --port 3003" echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" @@ -125,14 +139,16 @@ popd > /dev/null ## ## TODO: we should find a better way to wait for the nodes to be started -# Calculate the POSIX time 60 seconds from now. -REF_TIME_FOR_SLOT=$(( $(date +%s) + 60 )) +# Calculate the POSIX time 5 seconds from now. +REF_TIME_FOR_SLOT=$(( $(date +%s) + 5 )) -IMMDB_CMD_CORE="cabal run immdb-server \ +IMMDB_CMD_CORE="${immdb_server} \ -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --initial-slot 80 \ - --initial-time $REF_TIME_FOR_SLOT" + --initial-slot $REF_SLOT \ + --initial-time $REF_TIME_FOR_SLOT \ + --leios-schedule $LEIOS_SCHEDULE_PATH \ +" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -157,22 +173,22 @@ kill -9 -"$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" -# Log analysis +# # Log analysis -VENV_PATH="./scripts/leios-demo/venv" +# VENV_PATH="./scripts/leios-demo/venv" -# 1. Activate the Python Virtual Environment -if [ -f "$VENV_PATH/bin/activate" ]; then - echo "Activating virtual environment..." - # 'source' must be used for activation to modify the current shell environment - source "$VENV_PATH/bin/activate" -else - echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 -fi +# # 1. Activate the Python Virtual Environment +# if [ -f "$VENV_PATH/bin/activate" ]; then +# echo "Activating virtual environment..." +# # 'source' must be used for activation to modify the current shell environment +# source "$VENV_PATH/bin/activate" +# else +# echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 +# fi -python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log +# python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log -# 2. Deactivate the Python Virtual Environment before exiting -deactivate 2>/dev/null || true +# # 2. Deactivate the Python Virtual Environment before exiting +# deactivate 2>/dev/null || true -exit 0 +# exit 0 From 4b3cc38afee6bbae4c70c3c207bfbb4e9493829e Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 15:46:52 -0700 Subject: [PATCH 068/119] WIP my TODO list --- ouroboros-consensus/app/leiosdemo202510.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 1b073440b8..4b5e0e20d3 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -177,6 +177,14 @@ main2 = getArgs >>= \case \ OR $0 cache-copy my.db my.lfst bytesSize(positive)\n\ \" +{- TODO + +- all kinds of evictions? + +- disconnects? + +-} + reopenDb :: FilePath -> IO DB.Database reopenDb dbPath = do doesFileExist dbPath >>= \case From bf9731e218778942d0fccfb45a5f6173a6ebdefb Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 15:47:09 -0700 Subject: [PATCH 069/119] Revert "WIP the script" This reverts commit 9571dbf669465d9ced67a8174c4845087d2fdee4. --- scripts/leios-demo/leios-october-demo.sh | 94 ++++++++++-------------- 1 file changed, 39 insertions(+), 55 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index cb4ae874e3..e1bf1880ed 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -1,15 +1,21 @@ #!/bin/bash -# The only parameter should be the path to the folder +# The first parameter should be the path to the local checkout of +# cardano-node. +# +# The second parameter should be the path to the folder # where the data of a benchmarking cluster run is stored # (CLUSTER_RUN_DATA directory). -# P&T cluster run data +# Local checkout path of the cardano-node repository # Safely remove trailing slash if present -CLUSTER_RUN_DATA="${1%/}" +CARDANO_NODE_PATH="${1%/}" + +# P&T cluster run data +CLUSTER_RUN_DATA="${2%/}" -if [ "$#" -ne 1 ]; then - echo "Error: Please provide one parameter, the path to the cluster run data directory." >&2 +if [ "$#" -ne 2 ]; then + echo "Error: Please provide two parameters: and ." >&2 exit 1 fi @@ -23,26 +29,6 @@ if [ ! -d "$CLUSTER_RUN_DATA" ]; then exit 1 fi -if [[ -z "${cardano_node}" ]]; then - echo "Error: Please set \${cardano_node} to the path to the cardano-node exe." >&2 - exit 1 -fi - -if [[ -z "${immdb_server}" ]]; then - echo "Error: Please set \${immdb_server} to the path to the immdb-server exe." >&2 - exit 1 -fi - -if [[ -z "${REF_SLOT}" ]]; then - echo "Error: Please set \${REF_SLOT} to the reference slot." >&2 - exit 1 -fi - -if [[ -z "$LEIOS_SCHEDULE_PATH" ]]; then - echo "Error: Please set \${LEIOS_SCHEDULE_PATH} to path to the Leios schedule file." >&2 - exit 1 -fi - TMP_DIR=$(mktemp -d) echo "Using temporary directory for DB and logs: $TMP_DIR" @@ -52,8 +38,8 @@ pushd "$CARDANO_NODE_PATH" > /dev/null ## Run cardano-node (node-0) ## -echo "Creating topology-node-0.json in $(TMP_DIR)" -cat << EOF > "${TMP_DIR}/topology-node-0.json" +echo "Creating topology-node-0.json in $(pwd)" +cat << EOF > topology-node-0.json { "bootstrapPeers": [], "localRoots": [ @@ -75,11 +61,11 @@ EOF mkdir -p "$TMP_DIR/node-0/db" -CARDANO_NODE_CMD="${cardano_node} run \ +CARDANO_NODE_CMD="cabal run -- cardano-node run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --topology ${TMP_DIR}/topology-node-0.json \ + --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ - --socket-path $TMP_DIR/node-0.socket \ + --socket-path node-0.socket \ --host-addr 0.0.0.0 --port 3002" echo "Command: $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" @@ -94,7 +80,7 @@ echo "Cardano node 0 started with PID: $CARDANO_NODE_0_PID" ## Run a second Cardano-node (To be eventually replaced by a mocked downstream node) ## -cat << EOF > "${TMP_DIR}/topology-node-1.json" +cat << EOF > topology-node-1.json { "bootstrapPeers": [], "localRoots": [ @@ -116,11 +102,11 @@ EOF mkdir -p "$TMP_DIR/node-1/db" -MOCKED_PEER_CMD="${cardano-node} run \ +MOCKED_PEER_CMD="cabal run -- cardano-node run \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --topology ${TMP_DIR}/topology-node-1.json \ + --topology topology-node-1.json \ --database-path $TMP_DIR/node-1/db \ - --socket-path $TMP_DIR/node-1.socket \ + --socket-path node-1.socket \ --host-addr 0.0.0.0 --port 3003" echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" @@ -139,16 +125,14 @@ popd > /dev/null ## ## TODO: we should find a better way to wait for the nodes to be started -# Calculate the POSIX time 5 seconds from now. -REF_TIME_FOR_SLOT=$(( $(date +%s) + 5 )) +# Calculate the POSIX time 60 seconds from now. +REF_TIME_FOR_SLOT=$(( $(date +%s) + 60 )) -IMMDB_CMD_CORE="${immdb_server} \ +IMMDB_CMD_CORE="cabal run immdb-server \ -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ --config $CLUSTER_RUN_DATA/node-0/config.json \ - --initial-slot $REF_SLOT \ - --initial-time $REF_TIME_FOR_SLOT \ - --leios-schedule $LEIOS_SCHEDULE_PATH \ -" + --initial-slot 80 \ + --initial-time $REF_TIME_FOR_SLOT" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -173,22 +157,22 @@ kill -9 -"$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" -# # Log analysis +# Log analysis -# VENV_PATH="./scripts/leios-demo/venv" +VENV_PATH="./scripts/leios-demo/venv" -# # 1. Activate the Python Virtual Environment -# if [ -f "$VENV_PATH/bin/activate" ]; then -# echo "Activating virtual environment..." -# # 'source' must be used for activation to modify the current shell environment -# source "$VENV_PATH/bin/activate" -# else -# echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 -# fi +# 1. Activate the Python Virtual Environment +if [ -f "$VENV_PATH/bin/activate" ]; then + echo "Activating virtual environment..." + # 'source' must be used for activation to modify the current shell environment + source "$VENV_PATH/bin/activate" +else + echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 +fi -# python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log +python3 scripts/leios-demo/log_parser.py $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log -# # 2. Deactivate the Python Virtual Environment before exiting -# deactivate 2>/dev/null || true +# 2. Deactivate the Python Virtual Environment before exiting +deactivate 2>/dev/null || true -# exit 0 +exit 0 From a8bd0245e1604530c1f43d69b51ed7b38d84eb28 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 17:04:12 -0700 Subject: [PATCH 070/119] WIP hacking on script file --- scripts/leios-demo/leios-october-demo.sh | 151 ++++++++++++++--------- 1 file changed, 91 insertions(+), 60 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index f13ccbee6c..714f142327 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -1,35 +1,69 @@ #!/bin/bash -# The first parameter should be the path to the local checkout of -# cardano-node. -# -# The second parameter should be the path to the folder -# where the data of a benchmarking cluster run is stored -# (CLUSTER_RUN_DATA directory). - -# Local checkout path of the cardano-node repository -# Safely remove trailing slash if present -CARDANO_NODE_PATH="${1%/}" - -# P&T cluster run data -CLUSTER_RUN_DATA="${2%/}" - -if [ "$#" -ne 2 ]; then - echo "Error: Please provide two parameters: and ." >&2 +now=$(date +%s) + +if [[ -z "${NETSTAT_OUTPUT}" ]]; then + echo "Error: \${NETSTAT_OUTPUT} must be the path to the stdout of a recent call to netstat -lntp." >&2 exit 1 fi -if [ ! -d "$CARDANO_NODE_PATH" ]; then - echo "Error: Cardano node path '$CARDANO_NODE_PATH' not found or is not a directory." >&2 - exit 1 +if [[ ! "$SECONDS_UNTIL_REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$SECONDS_UNTIL_REF_SLOT" -le 0 ]]; then + echo "Error: \${SECONDS_UNTIL_REF_SLOT} must be a positive integer of seconds, which will be added to the execution time of this script." >&2 + exit 1 fi -if [ ! -d "$CLUSTER_RUN_DATA" ]; then +if [ ! -d "${CLUSTER_RUN_DATA%/}" ]; then + CLUSTER_RUN_DATA="${CLUSTER_RUN_DATA%/}" echo "Error: CLUSTER_RUN_DATA directory '$CLUSTER_RUN_DATA' not found or is not a directory." >&2 exit 1 fi -TMP_DIR=$(mktemp -d) +if [[ -z "${CARDANO_NODE}" ]]; then + echo "Error: \${CARDANO_NODE} must be the path to the cardano-node exe." >&2 + exit 1 +fi + +if [[ -z "${IMMDB_SERVER}" ]]; then + echo "Error: \${IMMDB_SERVER} must be the path to the immdb-server exe." >&2 + exit 1 +fi + +if [[ -z "${LEIOS_SCHEDULE}" ]]; then + echo "Error: \${LEIOS_SCHEDULE} must be the path to the JSON file that lists the schedule of Leios offers." >&2 + exit 1 +fi + +if [[ -z "${REF_SLOT}" ]] || [[ ! "$REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$REF_SLOT" -lt 0 ]]; then + echo "Error: \${REF_SLOT} must be a non-negative integer, a slot number" >&2 + exit 1 +fi + +find_random_unused_port() { + local port + local min_port=1024 # Start checking from non-privileged ports + local max_port=65535 # Maximum possible port number + + while true; do + # Generate a random port within the specified range + port=$(( RANDOM % (max_port - min_port + 1) + min_port )) + + # Check if the port is in use using netstat + # -l: listening sockets, -t: TCP, -n: numeric addresses, -p: show PID/program name + # grep -q: quiet mode, exits with 0 if match found, 1 otherwise + if ! cat ${NETSTAT_OUTPUT} | grep -q ":$port "; then + echo "$port" + return 0 # Port found, exit function + fi + done +} + +PORT1=$(find_random_unused_port) +PORT2=$(find_random_unused_port) +PORT3=$(find_random_unused_port) + +echo "Ports: ${PORT1} ${PORT2} ${PORT3}" + +TMP_DIR=$(mktemp -d ${TMPDIR:-/tmp}/leios-october-demo.XXXXXX) echo "Using temporary directory for DB and logs: $TMP_DIR" pushd "$CARDANO_NODE_PATH" > /dev/null @@ -47,7 +81,7 @@ cat << EOF > topology-node-0.json "accessPoints": [ { "address": "127.0.0.1", - "port": 3001 + "port": ${PORT1} } ], "advertise": false, @@ -61,12 +95,12 @@ EOF mkdir -p "$TMP_DIR/node-0/db" -CARDANO_NODE_CMD="cabal run -- cardano-node run \ - --config $CLUSTER_RUN_DATA/node-0/config.json \ +CARDANO_NODE_CMD="${CARDANO_NODE} run \ + --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ --socket-path node-0.socket \ - --host-addr 0.0.0.0 --port 3002" + --host-addr 0.0.0.0 --port ${PORT2}" echo "Command: $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" @@ -88,7 +122,7 @@ cat << EOF > topology-node-1.json "accessPoints": [ { "address": "127.0.0.1", - "port": 3002 + "port": ${PORT2} } ], "advertise": false, @@ -103,11 +137,11 @@ EOF mkdir -p "$TMP_DIR/node-1/db" MOCKED_PEER_CMD="cabal run -- cardano-node run \ - --config $CLUSTER_RUN_DATA/node-0/config.json \ + --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-1.json \ --database-path $TMP_DIR/node-1/db \ --socket-path node-1.socket \ - --host-addr 0.0.0.0 --port 3003" + --host-addr 0.0.0.0 --port ${PORT3}" echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" @@ -124,16 +158,15 @@ popd > /dev/null ## Run immdb-server ## -## TODO: we should find a better way to wait for the nodes to be started -# Calculate the POSIX time 60 seconds from now. -REF_TIME_FOR_SLOT=$(( $(date +%s) + 60 )) -INITIAL_SLOT=80 +ONSET_OF_REF_SLOT=$(( $now + ${SECONDS_UNTIL_REF_SLOT} )) -IMMDB_CMD_CORE="cabal run immdb-server \ - -- --db $CLUSTER_RUN_DATA/node-0/db/immutable/ \ - --config $CLUSTER_RUN_DATA/node-0/config.json \ - --initial-slot $INITIAL_SLOT \ - --initial-time $REF_TIME_FOR_SLOT" +IMMDB_CMD_CORE="${IMMDB_SERVER} \ + --db $CLUSTER_RUN_DATA/immdb-node/immutable/ \ + --config $CLUSTER_RUN_DATA/immdb-node/config.json \ + --initial-slot $REF_SLOT \ + --initial-time $ONSET_OF_REF_SLOT + --leios-schedule $LEIOS_SCHEDULE + --port ${PORT1}" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -143,40 +176,38 @@ IMMDB_SERVER_PID=$! echo "ImmDB server started with PID: $IMMDB_SERVER_PID" - -# TODO: we should change the condition on which we terminate the demo. -echo "Sleeping..." -sleep 120 +read -n 1 -s -r -p "Press any key to stop the spawned processes..." echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." kill "$IMMDB_SERVER_PID" 2>/dev/null || true # Use negative PID to target the process group ID and SIGKILL for cardano-node processes. -kill -9 -"$CARDANO_NODE_0_PID" 2>/dev/null || true -kill -9 -"$MOCKED_PEER_PID" 2>/dev/null || true +kill "$CARDANO_NODE_0_PID" 2>/dev/null || true + +kill "$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" -# Log analysis +# # Log analysis -VENV_PATH="./scripts/leios-demo/venv" +# VENV_PATH="./scripts/leios-demo/venv" -# 1. Activate the Python Virtual Environment -if [ -f "$VENV_PATH/bin/activate" ]; then - echo "Activating virtual environment..." - # 'source' must be used for activation to modify the current shell environment - source "$VENV_PATH/bin/activate" -else - echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 -fi +# # 1. Activate the Python Virtual Environment +# if [ -f "$VENV_PATH/bin/activate" ]; then +# echo "Activating virtual environment..." +# # 'source' must be used for activation to modify the current shell environment +# source "$VENV_PATH/bin/activate" +# else +# echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 +# fi -python3 scripts/leios-demo/log_parser.py \ - $INITIAL_SLOT $REF_TIME_FOR_SLOT \ - $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ - "scatter_plot.png" +# python3 scripts/leios-demo/log_parser.py \ +# $REF_SLOT $ONSET_OF_REF_SLOT \ +# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ +# "scatter_plot.png" -# 2. Deactivate the Python Virtual Environment before exiting -deactivate 2>/dev/null || true +# # 2. Deactivate the Python Virtual Environment before exiting +# deactivate 2>/dev/null || true -exit 0 +# exit 0 From 64d8c2c43540e69b808f99b9706c66ad84a7f0c6 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Fri, 24 Oct 2025 17:40:54 -0700 Subject: [PATCH 071/119] WIP fixup 291225921 LeiosSchedule parsing in immdb-server --- .../Cardano/Tools/ImmDBServer/Diffusion.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index 88b93ed778..9c8caa92c6 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -158,7 +158,7 @@ leiosScheduler getSlotDelay leiosContext = cnv (ebSlot, ebHashText, !mbEbBytesSize) = do let bytes = T.encodeUtf8 ebHashText ebHash <- - case fmap BL.fromStrict (BS16.decode bytes) >>= either (Left . show) Right . Serialise.deserialiseOrFail of + case BS16.decode bytes >>= either (Left . show) Right . Serialise.deserialiseOrFail . Serialise.serialise of Left err -> die $ "bad hash in Leios schedule! " ++ T.unpack ebHashText ++ " " ++ err Right y -> pure y let !rp = RealPoint (fromIntegral ebSlot) ebHash From 6c48bd8b506278fcce3dd5a58a50230653566723 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 07:17:00 -0700 Subject: [PATCH 072/119] leiosdemo202510: use in-mem table instead of batching retrievals --- ouroboros-consensus/app/leiosdemo202510.hs | 105 ++++++++++----------- 1 file changed, 49 insertions(+), 56 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 4b5e0e20d3..4006abd42f 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -31,7 +31,7 @@ import qualified Data.Foldable as Foldable import Data.Functor.Contravariant ((>$<)) import qualified Data.IntMap as IntMap import Data.IntMap (IntMap) -import Data.List (intercalate, isSuffixOf, unfoldr) +import Data.List (isSuffixOf, unfoldr) import Data.Map (Map) import Data.Maybe (fromMaybe) import qualified Data.Map.Strict as Map @@ -528,42 +528,38 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do die $ "An offset exceeds the theoretical limit " <> show idxLimit when (not $ and $ zipWith (<) idxs (tail idxs)) $ do die "Offsets not strictly ascending" - let numOffsets = sum $ map (Bits.popCount . snd) bitmaps let nextOffsetDESC = \case [] -> Nothing (idx, bitmap) : k -> case popRightmostOffset bitmap of Nothing -> nextOffsetDESC k Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) - offsets = unfoldr nextOffsetDESC (reverse bitmaps) - -- get the txs, at most 'maxBatchSize' at a time - -- - -- TODO Better workaround for requests of many txs? - stmt_lookup_ebClosuresMAIN <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (maxBatchSize `min` numOffsets) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresMAIN 1 (fromIntegralEbId ebId) + txOffsets = unfoldr nextOffsetDESC (reverse bitmaps) + -- fill in-memory table withDieMsg $ DB.exec db (fromString "BEGIN") - acc <- (\f -> foldM f emptyX (batches offsets)) $ \acc batch -> do - stmt <- - if numOffsets <= maxBatchSize || length batch == maxBatchSize then pure stmt_lookup_ebClosuresMAIN else do - -- this can only be reached for the last batch - withDie $ DB.finalize stmt_lookup_ebClosuresMAIN - stmt_lookup_ebClosuresTIDY <- withDieJust $ DB.prepare db $ fromString $ sql_lookup_ebClosures_DESC (numOffsets `mod` maxBatchSize) - withDie $ DB.bindInt64 stmt_lookup_ebClosuresTIDY 1 (fromIntegralEbId ebId) - pure stmt_lookup_ebClosuresTIDY - forM_ ([(2 :: DB.ParamIndex) ..] `zip` batch) $ \(i, offset) -> do - withDie $ DB.bindInt64 stmt i (fromIntegral offset) - acc' <- (\f -> foldM f acc batch) $ \acc' offset -> do - withDie (DB.stepNoCB stmt) >>= \case - DB.Done -> die $ "No rows starting at offset: " ++ show offset - DB.Row -> do - -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? - txOffset <- DB.columnInt64 stmt 0 - txBytes <- DB.columnBlob stmt 1 - when (txOffset /= fromIntegral offset) $ die $ "Missing offset: " <> show offset - pure $ pushX acc' txBytes - withDie $ DB.reset stmt - pure acc' + do + withDieMsg $ DB.exec db (fromString sql_attach_memTxPoints) + stmt <- withDieJust $ DB.prepare db (fromString sql_insert_memTxPoints) + withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) + forM_ txOffsets $ \txOffset -> do + withDie $ DB.bindInt64 stmt 2 (fromIntegral txOffset) + withDieDone $ DB.stepNoCB stmt + withDie $ DB.reset stmt + withDie $ DB.finalize stmt + -- get txBytess + stmt <- withDieJust $ DB.prepare db (fromString sql_retrieve_from_ebTxs) + acc <- (\f -> foldM f emptyX txOffsets) $ \acc txOffset -> do + withDie (DB.stepNoCB stmt) >>= \case + DB.Done -> pure acc + DB.Row -> do + txOffset' <- DB.columnInt64 stmt 0 + txBytes <- DB.columnBlob stmt 1 + when (fromIntegral txOffset /= txOffset') $ do + die $ "Missing offset " ++ show (txOffset, txOffset') + pure $ pushX acc txBytes + withDie $ DB.finalize stmt withDieMsg $ DB.exec db (fromString "COMMIT") + withDieMsg $ DB.exec db (fromString sql_detach_memTxPoints) -- combine the txs BS.putStr $ BS16.encode @@ -620,26 +616,16 @@ popRightmostOffset = \case in Just (63 - zs, Bits.clearBit w zs) --- | Never request more than this many txs simultaneously --- --- TODO confirm this prevents the query string from exceeding SQLite's size --- limits, even if the largest possible txOffsets are being requested. -maxBatchSize :: Int -maxBatchSize = 1024 - -batches :: [a] -> [[a]] -batches xs = if null xs then [] else take maxBatchSize xs : batches (drop maxBatchSize xs) - -- | It's DESCending because the accumulator within the -- 'msgLeiosBlockTxsRequest' logic naturally reverses it -sql_lookup_ebClosures_DESC :: Int -> String -sql_lookup_ebClosures_DESC n = - "SELECT txOffset, txBytes FROM ebTxs\n\ - \WHERE ebId = ? AND txBytes IS NOT NULL AND txOffset IN (" ++ hooks ++ ")\n\ - \ORDER BY txOffset DESC\n\ +sql_retrieve_from_ebTxs :: String +sql_retrieve_from_ebTxs = + "SELECT x.txOffset, x.txBytes\n\ + \FROM ebTxs as x\n\ + \INNER JOIN mem.txPoints ON x.ebId = mem.txPoints.ebId AND x.txOffset = mem.txPoints.txOffset\n\ + \WHERE x.txBytes IS NOT NULL\n\ + \ORDER BY x.txOffset DESC\n\ \" - where - hooks = intercalate "," (replicate n "?") ----- @@ -1660,14 +1646,16 @@ delIfZero x = if 0 == x then Nothing else Just x doCacheCopy :: DB.Database -> LeiosFetchState -> BytesSize -> IO LeiosFetchState doCacheCopy db lfst bytesSize = do - withDieMsg $ DB.exec db (fromString sql_attach_ebIds) + withDieMsg $ DB.exec db (fromString sql_attach_memTxPoints) withDieMsg $ DB.exec db (fromString "BEGIN") - stmt <- withDieJust $ DB.prepare db (fromString sql_insert_memEbIds) + stmt <- withDieJust $ DB.prepare db (fromString sql_insert_memTxPoints) -- load in-mem table of ebId-txOffset pairs lfst' <- go1 stmt 0 0 (toCopy lfst) + withDie $ DB.finalize stmt -- UPDATE JOIN driven by the loaded table withDieMsg $ DB.exec db (fromString sql_copy_from_txCache) withDieMsg $ DB.exec db (fromString "COMMIT") + withDieMsg $ DB.exec db (fromString sql_detach_memTxPoints) pure lfst' where go1 stmt !accBytesSize !accCount !acc @@ -1700,12 +1688,11 @@ doCacheCopy db lfst bytesSize = do toCopyCount = toCopyCount lfst - accCount } -sql_attach_ebIds :: String -sql_attach_ebIds = - -- NB :memory: databases are discarded when the SQLite connection is closed +sql_attach_memTxPoints :: String +sql_attach_memTxPoints = "ATTACH DATABASE ':memory:' AS mem;\n\ \\n\ - \CREATE TABLE mem.ebIds (\n\ + \CREATE TABLE mem.txPoints (\n\ \ ebId INTEGER NOT NULL\n\ \ ,\n\ \ txOffset INTEGER NOT NULL\n\ @@ -1714,9 +1701,15 @@ sql_attach_ebIds = \ ) WITHOUT ROWID;\n\ \" -sql_insert_memEbIds :: String -sql_insert_memEbIds = - "INSERT INTO mem.ebIds (ebId, txOffset) VALUES (?, ?);\n\ +sql_detach_memTxPoints :: String +sql_detach_memTxPoints = + -- NB :memory: databases are discarded when detached + "DETACH DATABASE mem;\n\ + \" + +sql_insert_memTxPoints :: String +sql_insert_memTxPoints = + "INSERT INTO mem.txPoints (ebId, txOffset) VALUES (?, ?);\n\ \" sql_copy_from_txCache :: String @@ -1724,5 +1717,5 @@ sql_copy_from_txCache = "UPDATE ebTxs\n\ \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = x.txHashBytes)\n\ \FROM ebTxs AS x\n\ - \INNER JOIN mem.ebIds ON x.ebId = mem.ebIds.ebId AND x.txOffset = mem.ebIds.txOffset\n\ + \INNER JOIN mem.txPoints ON x.ebId = mem.txPoints.ebId AND x.txOffset = mem.txPoints.txOffset\n\ \" From 350943efe470dc0c661a9619aa2b36a71932cfeb Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 09:01:57 -0700 Subject: [PATCH 073/119] leiosdemo202510: polishing model exe --- ouroboros-consensus/app/leiosdemo202510.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 4006abd42f..0c32041dff 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -1179,6 +1179,7 @@ loadLeiosFetchDynEnv = loadLeiosFetchDynEnvHelper True loadLeiosFetchDynEnvHelper :: Bool -> DB.Database -> IO LeiosFetchDynamicEnv loadLeiosFetchDynEnvHelper full db = do + withDieMsg $ DB.exec db (fromString "BEGIN") (ps, qs) <- do stmt <- withDieJust $ DB.prepare db (fromString sql_scan_ebId) let loop !ps !qs = @@ -1217,6 +1218,7 @@ loadLeiosFetchDynEnvHelper full db = do (Map.insertWith IntMap.union ebId (IntMap.singleton txOffset (txHash, txBytesSize)) bodies) (Map.insertWith Map.union txHash (Map.singleton ebId txOffset) offsetss) loop Set.empty Map.empty Map.empty + withDieMsg $ DB.exec db (fromString "COMMIT") pure MkLeiosFetchDynamicEnv { cachedTxs = cached , @@ -1563,20 +1565,23 @@ packRequests env dynEnv = fetchDecision2 :: DB.Database -> LeiosFetchState -> IO LeiosFetchState fetchDecision2 db acc0 = do - let env = MkLeiosFetchStaticEnv { - maxRequestedBytesSize = 50 * 10^(6 :: Int) + let million = 10^(6 :: Int) + millionBase2 = 2^(20 :: Int) + thousand = 10^(3 :: Int) + env = MkLeiosFetchStaticEnv { + maxRequestedBytesSize = 50 * million , - maxRequestedBytesSizePerPeer = 5 * 10^(6 :: Int) + maxRequestedBytesSizePerPeer = 5 * million , - maxRequestBytesSize = 500000 + maxRequestBytesSize = 500 * thousand , maxRequestsPerEb = 2 , maxRequestsPerTx = 2 , - maxToCopyBytesSize = 100 * 2^(20 :: Int) + maxToCopyBytesSize = 100 * millionBase2 , - maxToCopyCount = 100 * 10^(3 :: Int) + maxToCopyCount = 100 * thousand } dynEnv <- loadLeiosFetchDynEnv db let (acc1, MkLeiosFetchDecisions decisions) = leiosFetchLogicIteration env dynEnv acc0 From 6c0dbbe65382a48af2f92353e4baf07c2c7437bf Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 09:02:25 -0700 Subject: [PATCH 074/119] leiosdemo202510: adding Leios state to NodeKernel --- .../Ouroboros/Consensus/NodeKernel.hs | 34 +++++ ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../src/ouroboros-consensus/LeiosDemoTypes.hs | 141 ++++++++++++++++++ 3 files changed, 176 insertions(+) create mode 100644 ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 188ac9b4c2..a262f567b5 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -127,6 +127,13 @@ import Ouroboros.Network.TxSubmission.Mempool.Reader import qualified Ouroboros.Network.TxSubmission.Mempool.Reader as MempoolReader import System.Random (StdGen) +import Control.Concurrent.Class.MonadMVar (MVar) +import qualified Control.Concurrent.Class.MonadMVar as MVar +import Data.Map (Map) +import qualified Data.Map as Map + +import LeiosDemoTypes + {------------------------------------------------------------------------------- Relay node -------------------------------------------------------------------------------} @@ -177,6 +184,23 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { , getDiffusionPipeliningSupport :: DiffusionPipeliningSupport , getBlockchainTime :: BlockchainTime m + + -- ---------------------------------------- + + -- The following fields contain the information in the Leios model exe's + -- @LeiosFetchDynamicEnv@ and @LeiosFetchState@ data structures. + + -- See 'LeiosPeerMVars' for the write patterns + , getLeiosPeerMVars :: MVar m (Map (PeerId addrNTN) (LeiosPeerMVars m)) + -- written to by the LeiosNotify&LeiosFetch clients (TODO and by + -- eviction) + , getLeiosEbBodies :: MVar m LeiosEbBodies + -- written to by the fetch logic and by the LeiosNotify&LeiosFetch + -- clients (TODO and by eviction) + , getLeiosOutstanding :: MVar m (LeiosOutstanding addrNTN) + -- written to by the fetch logic and by the LeiosCopierThread + , getLeiosToCopy :: MVar m LeiosToCopy + } -- | Arguments required when initializing a node @@ -329,6 +353,11 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers fetchClientRegistry blockFetchConfiguration + getLeiosPeerMVars <- MVar.newMVar Map.empty + getLeiosEbBodies <- MVar.newMVar emptyLeiosEbBodies + getLeiosOutstanding <- MVar.newMVar emptyLeiosOutstanding + getLeiosToCopy <- MVar.newMVar emptyLeiosToCopy + return NodeKernel { getChainDB = chainDB , getMempool = mempool @@ -345,6 +374,11 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers = varOutboundConnectionsState , getDiffusionPipeliningSupport , getBlockchainTime = btime + + , getLeiosPeerMVars + , getLeiosEbBodies + , getLeiosOutstanding + , getLeiosToCopy } where blockForgingController :: InternalState m remotePeer localPeer blk diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index cca1bb4a7c..32c62bd556 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -69,6 +69,7 @@ library exposed-modules: LeiosDemoOnlyTestFetch LeiosDemoOnlyTestNotify + LeiosDemoTypes Ouroboros.Consensus.Block Ouroboros.Consensus.Block.Abstract Ouroboros.Consensus.Block.EBB diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs new file mode 100644 index 0000000000..d53de767cd --- /dev/null +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -0,0 +1,141 @@ +module LeiosDemoTypes (module LeiosDemoTypes) where + +import Cardano.Slotting.Slot (SlotNo) +import Control.Concurrent.Class.MonadMVar (MVar) +import Data.ByteString (ByteString) +import Data.IntMap (IntMap) +import qualified Data.IntMap as IntMap +import Data.Map (Map) +import qualified Data.Map as Map +import Data.Sequence (Seq) +import Data.Set (Set) +import qualified Data.Set as Set +import qualified Data.Vector as V +import Data.Word (Word16, Word32, Word64) + +type BytesSize = Word32 + +newtype EbId = MkEbId Int + deriving (Eq, Ord) + +newtype PeerId a = MkPeerId a + deriving (Eq, Ord) + +newtype EbHash = MkEbHash ByteString + +newtype TxHash = MkTxHash ByteString + +----- + +data LeiosFetchRequest = + LeiosBlockRequest LeiosBlockRequest + | + LeiosBlockTxsRequest LeiosBlockTxsRequest + +data LeiosBlockRequest = + -- | ebSlot, ebHash + MkLeiosBlockRequest + !SlotNo + !ByteString + +data LeiosBlockTxsRequest = + -- | ebSlot, ebHash, bitmaps, txHashes + -- + -- The hashes aren't sent to the peer, but they are used to validate the + -- reply when it arrives. + MkLeiosBlockTxsRequest + !SlotNo + !ByteString + [(Word16, Word64)] + !(V.Vector TxHash) + +----- + +-- +-- Compare the following data types to the @LeiosFetchDynamicEnv@ and +-- @LeiosFetchState@ types in the Leios model exe +-- +-- These data types are organized differently because they are organized by the +-- patterns of access to the "Ouroboros.Consensus.NodeKernel"'s shared state. +-- + +data LeiosPeerMVars m = MkLeiosPeerMVars { + -- written to only by the LeiosNotify client (TODO and eviction) + offerings :: !(MVar m (Set EbId, Set EbId)) + , + -- written to by the fetch logic and the LeiosFetch client + -- + -- These are the requests the fetch logic assumes will be sent, but have + -- not already been sent. + -- + -- Each client also maintains its own queue of requests that were + -- actually sent (ie dequeued from this sequence but their reply + -- hasn't yet arrived). + -- + -- Note that @requestedPerPeer@ is the list maintained per client, + -- whereas this list is not present in the model exe. + requestsToSend :: !(MVar m (Seq LeiosFetchRequest)) + } + +data LeiosEbBodies = MkLeiosEbBodies { + acquiredEbBodies :: !(Set EbId) + , + missingEbBodies :: !(Map EbId BytesSize) + , + ebPoints :: !(IntMap {- SlotNo -} (Map EbHash EbId)) + , + ebPointsInverse :: !(IntMap {- EbId -} EbHash) + } + +emptyLeiosEbBodies :: LeiosEbBodies +emptyLeiosEbBodies = + MkLeiosEbBodies + Set.empty + Map.empty + IntMap.empty + IntMap.empty + +data LeiosOutstanding pid = MkLeiosOutstanding { + requestedEbPeers :: !(Map EbId (Set (PeerId pid))) + , + requestedTxPeers :: !(Map TxHash (Set (PeerId pid))) + , + requestedBytesSizePerPeer :: !(Map (PeerId pid) BytesSize) + , + requestedBytesSize :: !BytesSize + , + -- TODO this might be far too big for the heap + cachedTxs :: !(Map TxHash BytesSize) + , + -- TODO this is far too big for the heap + missingTxBodies :: !(Set TxHash) + , + -- TODO this is far too big for the heap + ebBodies :: !(Map EbId (IntMap (TxHash, BytesSize))) + , + -- TODO this is far too big for the heap + txOffsetss :: !(Map TxHash (Map EbId Int)) + } + +emptyLeiosOutstanding :: LeiosOutstanding pid +emptyLeiosOutstanding = + MkLeiosOutstanding + Map.empty + Map.empty + Map.empty + 0 + Map.empty + Set.empty + Map.empty + Map.empty + +data LeiosToCopy = MkLeiosToCopy { + toCopy :: !(Map EbId (IntMap BytesSize)) + , + toCopyBytesSize :: !BytesSize + , + toCopyCount :: !Int + } + +emptyLeiosToCopy :: LeiosToCopy +emptyLeiosToCopy = MkLeiosToCopy Map.empty 0 0 From 6cefae19a586f31046056462bbd1c6d47aa964e2 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 09:24:36 -0700 Subject: [PATCH 075/119] leiosdemo202510: switch from RealPoint to bespoke LeiosPoint --- .../Cardano/Tools/ImmDBServer/Diffusion.hs | 16 +++++-------- .../Tools/ImmDBServer/MiniProtocols.hs | 7 +++--- .../Ouroboros/Consensus/Network/NodeToNode.hs | 15 ++++++------ .../src/ouroboros-consensus/LeiosDemoTypes.hs | 24 +++++++++++++++++++ 4 files changed, 42 insertions(+), 20 deletions(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index 9c8caa92c6..100ef64ce2 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -9,8 +9,6 @@ module Cardano.Tools.ImmDBServer.Diffusion (run, LeiosSchedule (..)) where import qualified Data.Aeson as Aeson -import Codec.Serialise (Serialise) -import qualified Codec.Serialise as Serialise import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, LeiosContext (..)) import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.ResourceRegistry @@ -50,6 +48,8 @@ import System.FS.API (SomeHasFS (..)) import System.FS.API.Types (MountPoint (MountPoint)) import System.FS.IO (ioHasFS) +import LeiosDemoTypes + -- | Glue code for using just the bits from the Diffusion Layer that we need in -- this context. serve :: @@ -85,8 +85,7 @@ serve sockAddr application = withIOManager \iocp -> do run :: forall blk. - ( Serialise (HeaderHash blk) - , GetPrevHash blk + ( GetPrevHash blk , ShowProxy blk , SupportedNetworkProtocolVersion blk , SerialiseNodeToNodeConstraints blk @@ -137,11 +136,9 @@ data LeiosSchedule = MkLeiosSchedule [(Double, (Word64, T.Text, Maybe Word32))] instance Aeson.FromJSON LeiosSchedule leiosScheduler :: - Serialise (HeaderHash blk) - => (Double -> IO DiffTime) -> - LeiosContext blk IO + LeiosContext IO -> LeiosSchedule -> @@ -156,10 +153,9 @@ leiosScheduler getSlotDelay leiosContext = mapM_ (MVar.putMVar (leiosMailbox leiosContext)) msgs where cnv (ebSlot, ebHashText, !mbEbBytesSize) = do - let bytes = T.encodeUtf8 ebHashText ebHash <- - case BS16.decode bytes >>= either (Left . show) Right . Serialise.deserialiseOrFail . Serialise.serialise of + case BS16.decode (T.encodeUtf8 ebHashText) of Left err -> die $ "bad hash in Leios schedule! " ++ T.unpack ebHashText ++ " " ++ err Right y -> pure y - let !rp = RealPoint (fromIntegral ebSlot) ebHash + let !rp = MkLeiosPoint (SlotNo ebSlot) (MkEbHash ebHash) pure (rp, mbEbBytesSize) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 2bb8f9458d..6a3d5fbcfd 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -69,6 +69,7 @@ import Ouroboros.Network.Protocol.KeepAlive.Server -- import LeiosDemoOnlyTestFetch import LeiosDemoOnlyTestNotify +import LeiosDemoTypes (LeiosPoint) immDBServer :: forall m blk addr. @@ -84,7 +85,7 @@ immDBServer :: -> ImmutableDB m blk -> NetworkMagic -> (SlotNo -> m DiffTime) - -> LeiosContext blk m + -> LeiosContext m -> Versions NodeToNodeVersion NodeToNodeVersionData (OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode addr BL.ByteString m Void ()) immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do @@ -297,6 +298,6 @@ data ImmDBServerException = ----- -data LeiosContext blk m = MkLeiosContext { - leiosMailbox :: MVar.MVar m (RealPoint blk, Maybe Word32) +data LeiosContext m = MkLeiosContext { + leiosMailbox :: MVar.MVar m (LeiosPoint, Maybe Word32) } diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index b724f57512..8b842a7f4a 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -133,6 +133,7 @@ import Ouroboros.Network.TxSubmission.Outbound import qualified Ouroboros.Network.Mux as ON -- import LeiosDemoOnlyTestFetch import LeiosDemoOnlyTestNotify +import LeiosDemoTypes (LeiosPoint, decodeLeiosPoint, encodeLeiosPoint) import Debug.Trace (traceM) {------------------------------------------------------------------------------- @@ -212,12 +213,12 @@ data Handlers m addr blk = Handlers { :: NodeToNodeVersion -> ControlMessageSTM m -> ConnectionId addr - -> LeiosNotifyClientPeerPipelined (RealPoint blk) () m () + -> LeiosNotifyClientPeerPipelined LeiosPoint () m () , hLeiosNotifyServer :: NodeToNodeVersion -> ConnectionId addr - -> LeiosNotifyServerPeer (RealPoint blk) () m () + -> LeiosNotifyServerPeer LeiosPoint () m () } mkHandlers :: @@ -315,7 +316,7 @@ data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS bLN = Codecs { , cTxSubmission2Codec :: Codec (TxSubmission2 (GenTxId blk) (GenTx blk)) e m bTX , cKeepAliveCodec :: Codec KeepAlive e m bKA , cPeerSharingCodec :: Codec (PeerSharing addr) e m bPS - , cLeiosNotifyCodec :: Codec (LeiosNotify (RealPoint blk) ()) e m bLN + , cLeiosNotifyCodec :: Codec (LeiosNotify LeiosPoint ()) e m bLN } -- | Protocol codecs for the node-to-node protocols @@ -376,8 +377,8 @@ defaultCodecs ccfg version encAddr decAddr nodeToNodeVersion = Codecs { , cLeiosNotifyCodec = codecLeiosNotify - (encodeRealPoint (encodeRawHash p)) - (decodeRealPoint (decodeRawHash p)) + encodeLeiosPoint + decodeLeiosPoint (\() -> CBOR.encodeNull) CBOR.decodeNull } @@ -401,7 +402,7 @@ identityCodecs :: Monad m (AnyMessage (TxSubmission2 (GenTxId blk) (GenTx blk))) (AnyMessage KeepAlive) (AnyMessage (PeerSharing addr)) - (AnyMessage (LeiosNotify (RealPoint blk) ())) + (AnyMessage (LeiosNotify LeiosPoint ())) identityCodecs = Codecs { cChainSyncCodec = codecChainSyncId , cChainSyncCodecSerialised = codecChainSyncId @@ -429,7 +430,7 @@ data Tracers' peer ntnAddr blk e f = Tracers { , tTxSubmission2Tracer :: f (TraceLabelPeer peer (TraceSendRecv (TxSubmission2 (GenTxId blk) (GenTx blk)))) , tKeepAliveTracer :: f (TraceLabelPeer peer (TraceSendRecv KeepAlive)) , tPeerSharingTracer :: f (TraceLabelPeer peer (TraceSendRecv (PeerSharing ntnAddr))) - , tLeiosNotifyTracer :: f (TraceLabelPeer peer (TraceSendRecv (LeiosNotify (RealPoint blk) ()))) + , tLeiosNotifyTracer :: f (TraceLabelPeer peer (TraceSendRecv (LeiosNotify LeiosPoint ()))) } instance (forall a. Semigroup (f a)) => Semigroup (Tracers' peer ntnAddr blk e f) where diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index d53de767cd..07e5e3d1a1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -1,6 +1,10 @@ module LeiosDemoTypes (module LeiosDemoTypes) where +import Cardano.Binary (enforceSize) import Cardano.Slotting.Slot (SlotNo) +import Codec.CBOR.Decoding (Decoder) +import Codec.CBOR.Encoding (Encoding, encodeListLen) +import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) import Data.ByteString (ByteString) import Data.IntMap (IntMap) @@ -10,8 +14,10 @@ import qualified Data.Map as Map import Data.Sequence (Seq) import Data.Set (Set) import qualified Data.Set as Set +import Data.String (fromString) import qualified Data.Vector as V import Data.Word (Word16, Word32, Word64) +import Ouroboros.Consensus.Util (ShowProxy (..)) type BytesSize = Word32 @@ -22,9 +28,27 @@ newtype PeerId a = MkPeerId a deriving (Eq, Ord) newtype EbHash = MkEbHash ByteString + deriving (Show) newtype TxHash = MkTxHash ByteString +data LeiosPoint = MkLeiosPoint SlotNo EbHash + deriving (Show) + +instance ShowProxy LeiosPoint where + showProxy _ = "LeiosPoint" + +encodeLeiosPoint :: LeiosPoint -> Encoding +encodeLeiosPoint (MkLeiosPoint ebSlot (MkEbHash ebHash)) = + encodeListLen 2 + <> encode ebSlot + <> encode ebHash + +decodeLeiosPoint :: Decoder s LeiosPoint +decodeLeiosPoint = do + enforceSize (fromString "LeiosPoint") 2 + MkLeiosPoint <$> decode <*> (MkEbHash <$> decode) + ----- data LeiosFetchRequest = From 2be294f8a0011f747c4194938c9276220fc367a7 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 10:05:17 -0700 Subject: [PATCH 076/119] leiosdemo202510: add basic logic to LeiosNotify client --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 66 +++++++++++++++---- .../Ouroboros/Consensus/NodeKernel.hs | 21 ++++-- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 3 +- 3 files changed, 71 insertions(+), 19 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 8b842a7f4a..343569ca4d 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} @@ -46,6 +47,7 @@ import qualified Codec.CBOR.Decoding as CBOR import Codec.CBOR.Encoding (Encoding) import qualified Codec.CBOR.Encoding as CBOR import Codec.CBOR.Read (DeserialiseFailure) +import qualified Control.Concurrent.Class.MonadMVar as MVar import qualified Control.Concurrent.Class.MonadSTM.Strict.TVar as TVar.Unchecked import Control.Monad.Class.MonadTime.SI (MonadTime) import Control.Monad.Class.MonadTimer.SI (MonadTimer) @@ -53,7 +55,7 @@ import Control.ResourceRegistry import Control.Tracer import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as BSL -import Data.Functor ((<&>)) +import Data.Functor ((<&>), void) import Data.Hashable (Hashable) import Data.Int (Int64) import Data.Map.Strict (Map) @@ -132,9 +134,12 @@ import Ouroboros.Network.TxSubmission.Outbound import qualified Ouroboros.Network.Mux as ON -- import LeiosDemoOnlyTestFetch -import LeiosDemoOnlyTestNotify -import LeiosDemoTypes (LeiosPoint, decodeLeiosPoint, encodeLeiosPoint) -import Debug.Trace (traceM) +import LeiosDemoOnlyTestNotify +import LeiosDemoTypes (LeiosPoint, decodeLeiosPoint, encodeLeiosPoint) +import qualified LeiosDemoTypes as Leios +import qualified Data.IntMap as IntMap +import qualified Data.Map as Map +import qualified Data.Set as Set {------------------------------------------------------------------------------- Handlers @@ -237,7 +242,7 @@ mkHandlers :: -> Handlers m addrNTN blk mkHandlers NodeKernelArgs {chainSyncFutureCheck, chainSyncHistoricityCheck, keepAliveRng, miniProtocolParameters, getDiffusionPipeliningSupport} - NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = + nodeKernel = Handlers { hChainSyncClient = \peer _isBigLedgerpeer dynEnv -> CsClient.chainSyncClient @@ -284,24 +289,59 @@ mkHandlers , hKeepAliveServer = \_version _peer -> keepAliveServer , hPeerSharingClient = \_version controlMessageSTM _peer -> peerSharingClient controlMessageSTM , hPeerSharingServer = \_version _peer -> peerSharingServer getPeerSharingAPI - , hLeiosNotifyClient = \_version controlMessageSTM _peer -> + , hLeiosNotifyClient = \_version controlMessageSTM peer -> leiosNotifyClientPeerPipelined (atomically controlMessageSTM <&> \case Terminate -> Left () _ -> Right 300 {- TODO magic number -}) (\case - MsgLeiosBlockAnnouncement{} -> pure () -- TODO - MsgLeiosBlockOffer _ sz -> do - traceM $ "MsgLeiosBlockOffer " ++ show sz - pure () -- TODO - MsgLeiosBlockTxsOffer{} -> do - traceM "MsgLeiosBlockTxsOffer" - pure () -- TODO + MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" + MsgLeiosBlockOffer p ebBytesSize -> do + let Leios.MkLeiosPoint (SlotNo slot64) ebHash = p + ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies -> do + ebId <- case IntMap.lookup (fromIntegral slot64) (Leios.ebPoints ebBodies) >>= Map.lookup ebHash of + Nothing -> error "TODO" + Just x -> pure x + let !ebBodies' = + if Set.member ebId (Leios.acquiredEbBodies ebBodies) then ebBodies else + ebBodies { + Leios.missingEbBodies = + Map.insert ebId ebBytesSize (Leios.missingEbBodies ebBodies) + } + pure (ebBodies', ebId) + peerMVars <- do + peersMVars <- MVar.readMVar getLeiosPeersMVars + case Map.lookup (Leios.MkPeerId peer) peersMVars of + Nothing -> error "TODO" + Just x -> pure x + MVar.modifyMVar_ (Leios.offerings peerMVars) $ \(offers1, offers2) -> do + let !offers1' = Set.insert ebId offers1 + pure (offers1', offers2) + void $ MVar.tryPutMVar getLeiosReady () + MsgLeiosBlockTxsOffer p -> do + let Leios.MkLeiosPoint (SlotNo slot64) ebHash = p + ebId <- do + ebBodies <- MVar.readMVar getLeiosEbBodies + case IntMap.lookup (fromIntegral slot64) (Leios.ebPoints ebBodies) >>= Map.lookup ebHash of + Nothing -> error "TODO" + Just x -> pure x + peerMVars <- do + peersMVars <- MVar.readMVar getLeiosPeersMVars + case Map.lookup (Leios.MkPeerId peer) peersMVars of + Nothing -> error "TODO" + Just x -> pure x + MVar.modifyMVar_ (Leios.offerings peerMVars) $ \(offers1, offers2) -> do + let !offers2' = Set.insert ebId offers2 + pure (offers1, offers2') + void $ MVar.tryPutMVar getLeiosReady () ) , hLeiosNotifyServer = \_version _peer -> leiosNotifyServerPeer (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO } + where + NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel + NodeKernel {getLeiosPeersMVars, getLeiosEbBodies, getLeiosReady} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index a262f567b5..0e9ad91244 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -189,17 +189,26 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- The following fields contain the information in the Leios model exe's -- @LeiosFetchDynamicEnv@ and @LeiosFetchState@ data structures. + -- + -- TODO this could all use TVars, but I'm curious whether MVars are a + -- noticeably awkward fit for this logic. -- See 'LeiosPeerMVars' for the write patterns - , getLeiosPeerMVars :: MVar m (Map (PeerId addrNTN) (LeiosPeerMVars m)) + , getLeiosPeersMVars :: MVar m (Map (PeerId (ConnectionId addrNTN)) (LeiosPeerMVars m)) -- written to by the LeiosNotify&LeiosFetch clients (TODO and by -- eviction) , getLeiosEbBodies :: MVar m LeiosEbBodies -- written to by the fetch logic and by the LeiosNotify&LeiosFetch -- clients (TODO and by eviction) - , getLeiosOutstanding :: MVar m (LeiosOutstanding addrNTN) - -- written to by the fetch logic and by the LeiosCopierThread + , getLeiosOutstanding :: MVar m (LeiosOutstanding (ConnectionId addrNTN)) + -- written to by the fetch logic and by the LeiosCopier , getLeiosToCopy :: MVar m LeiosToCopy + -- | Leios fetch logic 'MVar.takeMVar's before it runs + -- + -- LeiosNotify clients, LeiosFetch clients, and the LeiosCopier + -- 'MVar.tryPutMVar' whenever they make a change that might unblock a new + -- fetch decision. + , getLeiosReady :: MVar m () } @@ -353,10 +362,11 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers fetchClientRegistry blockFetchConfiguration - getLeiosPeerMVars <- MVar.newMVar Map.empty + getLeiosPeersMVars <- MVar.newMVar Map.empty getLeiosEbBodies <- MVar.newMVar emptyLeiosEbBodies getLeiosOutstanding <- MVar.newMVar emptyLeiosOutstanding getLeiosToCopy <- MVar.newMVar emptyLeiosToCopy + getLeiosReady <- MVar.newEmptyMVar return NodeKernel { getChainDB = chainDB @@ -375,10 +385,11 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getDiffusionPipeliningSupport , getBlockchainTime = btime - , getLeiosPeerMVars + , getLeiosPeersMVars , getLeiosEbBodies , getLeiosOutstanding , getLeiosToCopy + , getLeiosReady } where blockForgingController :: InternalState m remotePeer localPeer blk diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 07e5e3d1a1..f76ff1b824 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -28,9 +28,10 @@ newtype PeerId a = MkPeerId a deriving (Eq, Ord) newtype EbHash = MkEbHash ByteString - deriving (Show) + deriving (Eq, Ord, Show) newtype TxHash = MkTxHash ByteString + deriving (Eq, Ord) data LeiosPoint = MkLeiosPoint SlotNo EbHash deriving (Show) From 6efd6d87af25e86ddfa17c3ce7f733774f52faa5 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 10:51:15 -0700 Subject: [PATCH 077/119] leiosdemo202510: migrate EbId logic from the model exe --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 28 +++----- ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../src/ouroboros-consensus/LeiosDemoLogic.hs | 68 +++++++++++++++++++ 3 files changed, 80 insertions(+), 17 deletions(-) create mode 100644 ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 343569ca4d..33fd517d8a 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -137,8 +137,9 @@ import qualified Ouroboros.Network.Mux as ON import LeiosDemoOnlyTestNotify import LeiosDemoTypes (LeiosPoint, decodeLeiosPoint, encodeLeiosPoint) import qualified LeiosDemoTypes as Leios -import qualified Data.IntMap as IntMap +import qualified LeiosDemoLogic as Leios import qualified Data.Map as Map +import Data.Maybe (fromMaybe) import qualified Data.Set as Set {------------------------------------------------------------------------------- @@ -297,18 +298,16 @@ mkHandlers (\case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do - let Leios.MkLeiosPoint (SlotNo slot64) ebHash = p - ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies -> do - ebId <- case IntMap.lookup (fromIntegral slot64) (Leios.ebPoints ebBodies) >>= Map.lookup ebHash of - Nothing -> error "TODO" - Just x -> pure x - let !ebBodies' = - if Set.member ebId (Leios.acquiredEbBodies ebBodies) then ebBodies else - ebBodies { + ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do + let (ebId, mbEbBodies2) = Leios.ebIdFromPoint p ebBodies1 + ebBodies2 = fromMaybe ebBodies1 mbEbBodies2 + let !ebBodies3 = + if Set.member ebId (Leios.acquiredEbBodies ebBodies2) then ebBodies2 else + ebBodies2 { Leios.missingEbBodies = - Map.insert ebId ebBytesSize (Leios.missingEbBodies ebBodies) + Map.insert ebId ebBytesSize (Leios.missingEbBodies ebBodies2) } - pure (ebBodies', ebId) + pure (ebBodies3, ebId) peerMVars <- do peersMVars <- MVar.readMVar getLeiosPeersMVars case Map.lookup (Leios.MkPeerId peer) peersMVars of @@ -319,12 +318,7 @@ mkHandlers pure (offers1', offers2) void $ MVar.tryPutMVar getLeiosReady () MsgLeiosBlockTxsOffer p -> do - let Leios.MkLeiosPoint (SlotNo slot64) ebHash = p - ebId <- do - ebBodies <- MVar.readMVar getLeiosEbBodies - case IntMap.lookup (fromIntegral slot64) (Leios.ebPoints ebBodies) >>= Map.lookup ebHash of - Nothing -> error "TODO" - Just x -> pure x + ebId <- Leios.ebIdFromPointM getLeiosEbBodies p peerMVars <- do peersMVars <- MVar.readMVar getLeiosPeersMVars case Map.lookup (Leios.MkPeerId peer) peersMVars of diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 32c62bd556..c28c523c6e 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -67,6 +67,7 @@ library import: common-lib hs-source-dirs: src/ouroboros-consensus exposed-modules: + LeiosDemoLogic LeiosDemoOnlyTestFetch LeiosDemoOnlyTestNotify LeiosDemoTypes diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs new file mode 100644 index 0000000000..addae43472 --- /dev/null +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -0,0 +1,68 @@ +{-# LANGUAGE BangPatterns #-} + +module LeiosDemoLogic (module LeiosDemoLogic) where + +import Cardano.Slotting.Slot (SlotNo (..)) +import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) +import qualified Control.Concurrent.Class.MonadMVar as MVar +import qualified Data.Bits as Bits +import Data.Functor ((<&>)) +import qualified Data.IntMap as IntMap +import qualified Data.Map as Map +import Data.Word (Word64) +import LeiosDemoTypes (EbId (..), LeiosEbBodies, LeiosPoint (..)) +import qualified LeiosDemoTypes as Leios + +ebIdSlot :: EbId -> SlotNo +ebIdSlot (MkEbId y) = + SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) + +ebIdToPoint :: EbId -> LeiosEbBodies -> Maybe LeiosPoint +ebIdToPoint (MkEbId i) x = + (\h -> MkLeiosPoint (ebIdSlot (MkEbId i)) h) + <$> + IntMap.lookup i (Leios.ebPointsInverse x) + +ebIdToPointM :: MonadMVar m => MVar m LeiosEbBodies -> EbId -> m (Maybe LeiosPoint) +ebIdToPointM mvar ebId = + MVar.readMVar mvar <&> ebIdToPoint ebId + +ebIdFromPoint :: LeiosPoint -> LeiosEbBodies -> (EbId, Maybe LeiosEbBodies) +ebIdFromPoint p x = + case IntMap.lookup islot (Leios.ebPoints x) of + Just m -> case Map.lookup ebHash m of + Just y -> (y, Nothing) + Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) - Map.size m + Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) + where + MkLeiosPoint ebSlot ebHash = p + SlotNo wslot = ebSlot + islot = fromIntegral (wslot :: Word64) + + zero = fromIntegral (wslot `Bits.unsafeShiftL` 20) + minBound :: Int + + gen y = + let !x' = x { + Leios.ebPoints = + IntMap.insertWith + Map.union + islot + (Map.singleton ebHash y) + (Leios.ebPoints x) + , + Leios.ebPointsInverse = + let MkEbId z = y + in + IntMap.insert z ebHash (Leios.ebPointsInverse x) + } + in (y, Just x') + +ebIdFromPointM :: MonadMVar m => MVar m LeiosEbBodies -> LeiosPoint -> m EbId +ebIdFromPointM mvar p = + MVar.modifyMVar mvar $ \ebBodies -> do + let (ebId, mbEbBodies') = ebIdFromPoint p ebBodies + case mbEbBodies' of + Nothing -> pure (ebBodies, ebId) + Just ebBodies' -> do + -- TODO when to INSERT INTO ebPoints? + pure (ebBodies', ebId) From 6f2a6af071139e6f483bd29a3298eaf4d66c1b40 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 12:18:19 -0700 Subject: [PATCH 078/119] fixup leiosdemo202510: LeiosNotify --- .../LeiosDemoOnlyTestNotify.hs | 95 +++++++++---------- 1 file changed, 47 insertions(+), 48 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index db401d8807..806736d988 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -34,21 +34,20 @@ module LeiosDemoOnlyTestNotify import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR -import Control.DeepSeq (NFData (..)) -import Control.Monad.Class.MonadST -import Data.ByteString.Lazy (ByteString) -import Data.Functor ((<&>)) -import Data.Kind (Type) -import Data.Singletons -import Data.Word (Word32) +import Control.DeepSeq (NFData (..)) +import Control.Monad.Class.MonadST +import Data.ByteString.Lazy (ByteString) +import Data.Functor ((<&>)) +import Data.Kind (Type) +import Data.Singletons +import Data.Word (Word32) import qualified Network.Mux.Types as Mux -import Network.TypedProtocol.Codec.CBOR -import Network.TypedProtocol.Core -import Network.TypedProtocol.Peer --- import Network.TypedProtocol.Peer.Client -import Ouroboros.Network.Protocol.Limits -import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) -import Text.Printf +import Network.TypedProtocol.Codec.CBOR +import Network.TypedProtocol.Core +import Network.TypedProtocol.Peer +import Ouroboros.Network.Protocol.Limits +import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) +import Text.Printf ----- @@ -310,27 +309,51 @@ leiosNotifyClientPeer :: forall m announcement point a. Monad m => - m (Maybe a) - -> - (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) + m (Either a (Message (LeiosNotify point announcement) StBusy StIdle -> m ())) -> Peer (LeiosNotify point announcement) AsClient NonPipelined StIdle m a -leiosNotifyClientPeer checkDone handler = +leiosNotifyClientPeer checkDone = go where go :: Peer (LeiosNotify point announcement) AsClient NonPipelined StIdle m a go = Effect $ checkDone <&> \case - Just x -> + Left x -> Yield ReflClientAgency MsgDone $ Done ReflNobodyAgency x - Nothing -> + Right k -> Yield ReflClientAgency MsgLeiosNotificationRequestNext $ Await ReflServerAgency $ \msg -> case msg of - MsgLeiosBlockAnnouncement{} -> react msg - MsgLeiosBlockOffer{} -> react msg - MsgLeiosBlockTxsOffer{} -> react msg + MsgLeiosBlockAnnouncement{} -> react $ k msg + MsgLeiosBlockOffer{} -> react $ k msg + MsgLeiosBlockTxsOffer{} -> react $ k msg - react msg = Effect $ fmap (\() -> go) $ handler msg + react action = Effect $ fmap (\() -> go) action + +----- + +type LeiosNotifyServerPeer point announcement m a = + Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () + +leiosNotifyServerPeer :: + forall m announcement point. + Monad m + => + m (Message (LeiosNotify point announcement) StBusy StIdle) + -> + Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () +leiosNotifyServerPeer handler = + go + where + go :: Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () + go = Await ReflClientAgency $ \case + MsgDone -> Done ReflNobodyAgency () + MsgLeiosNotificationRequestNext -> Effect $ do + msg <- handler + pure + $ Yield ReflServerAgency msg + $ go + +----- -- | Merely an abbrevation local to this module type X point announcement m a n = @@ -389,27 +412,3 @@ leiosNotifyClientPeerPipelined checkDone handler = Collect Nothing (\(MkC action) -> Effect $ do action; pure $ drainThePipe x m) - ------ - -type LeiosNotifyServerPeer point announcement m a = - Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () - -leiosNotifyServerPeer :: - forall m announcement point a. - Monad m - => - m (Message (LeiosNotify point announcement) StBusy StIdle) - -> - Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () -leiosNotifyServerPeer handler = - go - where - go :: Peer (LeiosNotify point announcement) AsServer NonPipelined StIdle m () - go = Await ReflClientAgency $ \msg -> case msg of - MsgDone -> Done ReflNobodyAgency () - MsgLeiosNotificationRequestNext -> Effect $ do - msg <- handler - pure - $ Yield ReflServerAgency msg - $ go From 40cddd10871a918180d045cb21c02395c04b810f Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 12:19:37 -0700 Subject: [PATCH 079/119] leiosdemo202510: add LeiosFetch to NodeToNode --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 137 ++++++++++++--- .../Ouroboros/Consensus/Node.hs | 2 + .../LeiosDemoOnlyTestFetch.hs | 158 +++++++++++++----- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 50 +++++- 4 files changed, 277 insertions(+), 70 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 33fd517d8a..2fbea19c1c 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -132,15 +132,15 @@ import Ouroboros.Network.TxSubmission.Mempool.Reader import Ouroboros.Network.TxSubmission.Outbound -import qualified Ouroboros.Network.Mux as ON --- import LeiosDemoOnlyTestFetch -import LeiosDemoOnlyTestNotify -import LeiosDemoTypes (LeiosPoint, decodeLeiosPoint, encodeLeiosPoint) -import qualified LeiosDemoTypes as Leios -import qualified LeiosDemoLogic as Leios import qualified Data.Map as Map import Data.Maybe (fromMaybe) import qualified Data.Set as Set +import LeiosDemoOnlyTestFetch +import LeiosDemoOnlyTestNotify +import LeiosDemoTypes (LeiosEb, LeiosPoint, LeiosTx) +import qualified LeiosDemoTypes as Leios +import qualified LeiosDemoLogic as Leios +import qualified Ouroboros.Network.Mux as ON {------------------------------------------------------------------------------- Handlers @@ -225,6 +225,18 @@ data Handlers m addr blk = Handlers { :: NodeToNodeVersion -> ConnectionId addr -> LeiosNotifyServerPeer LeiosPoint () m () + + , hLeiosFetchClient + :: NodeToNodeVersion + -> ControlMessageSTM m + -> ConnectionId addr + -> LeiosFetchClientPeer LeiosPoint LeiosEb LeiosTx m () + + , hLeiosFetchServer + :: NodeToNodeVersion + -> ConnectionId addr + -> LeiosFetchServerPeer LeiosPoint LeiosEb LeiosTx m () + } mkHandlers :: @@ -332,6 +344,15 @@ mkHandlers , hLeiosNotifyServer = \_version _peer -> leiosNotifyServerPeer (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO + , hLeiosFetchClient = \_version controlMessageSTM _peer -> + leiosFetchClientPeer + (atomically $ controlMessageSTM >>= \case + Terminate -> pure $ Left () + _ -> retry + ) -- TODO + , hLeiosFetchServer = \_version _peer -> + leiosFetchServerPeer + (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel @@ -342,7 +363,7 @@ mkHandlers -------------------------------------------------------------------------------} -- | Node-to-node protocol codecs needed to run 'Handlers'. -data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS bLN = Codecs { +data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS bLN bLF = Codecs { cChainSyncCodec :: Codec (ChainSync (Header blk) (Point blk) (Tip blk)) e m bCS , cChainSyncCodecSerialised :: Codec (ChainSync (SerialisedHeader blk) (Point blk) (Tip blk)) e m bSCS , cBlockFetchCodec :: Codec (BlockFetch blk (Point blk)) e m bBF @@ -351,6 +372,7 @@ data Codecs blk addr e m bCS bSCS bBF bSBF bTX bKA bPS bLN = Codecs { , cKeepAliveCodec :: Codec KeepAlive e m bKA , cPeerSharingCodec :: Codec (PeerSharing addr) e m bPS , cLeiosNotifyCodec :: Codec (LeiosNotify LeiosPoint ()) e m bLN + , cLeiosFetchCodec :: Codec (LeiosFetch LeiosPoint LeiosEb LeiosTx) e m bLF } -- | Protocol codecs for the node-to-node protocols @@ -364,7 +386,7 @@ defaultCodecs :: forall m blk addr. -> (NodeToNodeVersion -> forall s . CBOR.Decoder s addr) -> NodeToNodeVersion -> Codecs blk addr DeserialiseFailure m - ByteString ByteString ByteString ByteString ByteString ByteString ByteString ByteString + ByteString ByteString ByteString ByteString ByteString ByteString ByteString ByteString ByteString defaultCodecs ccfg version encAddr decAddr nodeToNodeVersion = Codecs { cChainSyncCodec = codecChainSync @@ -411,10 +433,19 @@ defaultCodecs ccfg version encAddr decAddr nodeToNodeVersion = Codecs { , cLeiosNotifyCodec = codecLeiosNotify - encodeLeiosPoint - decodeLeiosPoint + Leios.encodeLeiosPoint + Leios.decodeLeiosPoint (\() -> CBOR.encodeNull) CBOR.decodeNull + + , cLeiosFetchCodec = + codecLeiosFetch + Leios.encodeLeiosPoint + Leios.decodeLeiosPoint + Leios.encodeLeiosEb + Leios.decodeLeiosEb + Leios.encodeLeiosTx + Leios.decodeLeiosTx } where p :: Proxy blk @@ -437,6 +468,7 @@ identityCodecs :: Monad m (AnyMessage KeepAlive) (AnyMessage (PeerSharing addr)) (AnyMessage (LeiosNotify LeiosPoint ())) + (AnyMessage (LeiosFetch LeiosPoint LeiosEb LeiosTx)) identityCodecs = Codecs { cChainSyncCodec = codecChainSyncId , cChainSyncCodecSerialised = codecChainSyncId @@ -446,6 +478,7 @@ identityCodecs = Codecs { , cKeepAliveCodec = codecKeepAliveId , cPeerSharingCodec = codecPeerSharingId , cLeiosNotifyCodec = codecLeiosNotifyId + , cLeiosFetchCodec = codecLeiosFetchId } {------------------------------------------------------------------------------- @@ -465,6 +498,7 @@ data Tracers' peer ntnAddr blk e f = Tracers { , tKeepAliveTracer :: f (TraceLabelPeer peer (TraceSendRecv KeepAlive)) , tPeerSharingTracer :: f (TraceLabelPeer peer (TraceSendRecv (PeerSharing ntnAddr))) , tLeiosNotifyTracer :: f (TraceLabelPeer peer (TraceSendRecv (LeiosNotify LeiosPoint ()))) + , tLeiosFetchTracer :: f (TraceLabelPeer peer (TraceSendRecv (LeiosFetch LeiosPoint LeiosEb LeiosTx))) } instance (forall a. Semigroup (f a)) => Semigroup (Tracers' peer ntnAddr blk e f) where @@ -477,6 +511,7 @@ instance (forall a. Semigroup (f a)) => Semigroup (Tracers' peer ntnAddr blk e f , tKeepAliveTracer = f tKeepAliveTracer , tPeerSharingTracer = f tPeerSharingTracer , tLeiosNotifyTracer = f tLeiosNotifyTracer + , tLeiosFetchTracer = f tLeiosFetchTracer } where f :: forall a. Semigroup a @@ -495,6 +530,7 @@ nullTracers = Tracers { , tKeepAliveTracer = nullTracer , tPeerSharingTracer = nullTracer , tLeiosNotifyTracer = nullTracer + , tLeiosFetchTracer = nullTracer } showTracers :: ( Show blk @@ -515,6 +551,7 @@ showTracers tr = Tracers { , tKeepAliveTracer = showTracing tr , tPeerSharingTracer = showTracing tr , tLeiosNotifyTracer = showTracing tr + , tLeiosFetchTracer = showTracing tr } {------------------------------------------------------------------------------- @@ -537,7 +574,7 @@ type ServerApp m addr bytes a = -- | Applications for the node-to-node protocols -- -- See 'Network.Mux.Types.MuxApplication' -data Apps m addr bCS bBF bTX bKA bPS bLN a b = Apps { +data Apps m addr bCS bBF bTX bKA bPS bLN bLF a b = Apps { -- | Start a chain sync client that communicates with the given upstream -- node. aChainSyncClient :: ClientApp m addr bCS a @@ -576,6 +613,12 @@ data Apps m addr bCS bBF bTX bKA bPS bLN a b = Apps { -- | Start a LeiosNotify server. , aLeiosNotifyServer :: ServerApp m addr bLN b + + -- | Start a LeiosFetch client. + , aLeiosFetchClient :: ClientApp m addr bLF a + + -- | Start a LeiosFetch server. + , aLeiosFetchServer :: ServerApp m addr bLF b } @@ -585,7 +628,7 @@ data Apps m addr bCS bBF bTX bKA bPS bLN a b = Apps { -- They don't depend on the instantiation of the protocol parameters (which -- block type is used, etc.), hence the use of 'RankNTypes'. -- -data ByteLimits bCS bBF bTX bKA bLN = ByteLimits { +data ByteLimits bCS bBF bTX bKA bLN bLF = ByteLimits { blChainSync :: forall header point tip. ProtocolSizeLimits (ChainSync header point tip) @@ -610,24 +653,31 @@ data ByteLimits bCS bBF bTX bKA bLN = ByteLimits { (LeiosNotify point announcement) bLN + , blLeiosFetch :: forall point eb tx. + ProtocolSizeLimits + (LeiosFetch point eb tx) + bLF + } -noByteLimits :: ByteLimits bCS bBF bTX bKA bLN +noByteLimits :: ByteLimits bCS bBF bTX bKA bLN bLF noByteLimits = ByteLimits { blChainSync = byteLimitsChainSync (const 0) , blBlockFetch = byteLimitsBlockFetch (const 0) , blTxSubmission2 = byteLimitsTxSubmission2 (const 0) , blKeepAlive = byteLimitsKeepAlive (const 0) , blLeiosNotify = byteLimitsLeiosNotify (const 0) + , blLeiosFetch = byteLimitsLeiosFetch (const 0) } -byteLimits :: ByteLimits ByteString ByteString ByteString ByteString ByteString +byteLimits :: ByteLimits ByteString ByteString ByteString ByteString ByteString ByteString byteLimits = ByteLimits { blChainSync = byteLimitsChainSync size , blBlockFetch = byteLimitsBlockFetch size , blTxSubmission2 = byteLimitsTxSubmission2 size , blKeepAlive = byteLimitsKeepAlive size , blLeiosNotify = byteLimitsLeiosNotify size + , blLeiosFetch = byteLimitsLeiosFetch size } where size :: ByteString -> Word @@ -636,7 +686,7 @@ byteLimits = ByteLimits { -- | Construct the 'NetworkApplication' for the node-to-node protocols mkApps :: - forall m addrNTN addrNTC blk e bCS bBF bTX bKA bPS bLN. + forall m addrNTN addrNTC blk e bCS bBF bTX bKA bPS bLN bLF. ( IOLike m , MonadTimer m , Ord addrNTN @@ -649,14 +699,14 @@ mkApps :: ) => NodeKernel m addrNTN addrNTC blk -- ^ Needed for bracketing only -> Tracers m addrNTN blk e - -> (NodeToNodeVersion -> Codecs blk addrNTN e m bCS bCS bBF bBF bTX bKA bPS bLN) - -> ByteLimits bCS bBF bTX bKA bLN + -> (NodeToNodeVersion -> Codecs blk addrNTN e m bCS bCS bBF bBF bTX bKA bPS bLN bLF) + -> ByteLimits bCS bBF bTX bKA bLN bLF -> m ChainSyncTimeout -> CsClient.ChainSyncLoPBucketConfig -> CsClient.CSJConfig -> ReportPeerMetrics m (ConnectionId addrNTN) -> Handlers m addrNTN blk - -> Apps m addrNTN bCS bBF bTX bKA bPS bLN NodeToNodeInitiatorResult () + -> Apps m addrNTN bCS bBF bTX bKA bPS bLN bLF NodeToNodeInitiatorResult () mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucketConfig csjConfig ReportPeerMetrics {..} Handlers {..} = Apps {..} where @@ -934,6 +984,40 @@ mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucke channel $ hLeiosNotifyServer version them + aLeiosFetchClient + :: NodeToNodeVersion + -> ExpandedInitiatorContext addrNTN m + -> Channel m bLF + -> m (NodeToNodeInitiatorResult, Maybe bLF) + aLeiosFetchClient version ExpandedInitiatorContext { + eicConnectionId = them, + eicControlMessage = controlMessageSTM + } channel = do + labelThisThread "LeiosFetchClient" + ((), trailing) <- runPeerWithLimits + (TraceLabelPeer them `contramap` tLeiosFetchTracer) + (cLeiosFetchCodec (mkCodecs version)) + blLeiosFetch + timeLimitsLeiosFetch + channel + $ hLeiosFetchClient version controlMessageSTM them + pure (NoInitiatorResult, trailing) + + aLeiosFetchServer + :: NodeToNodeVersion + -> ResponderContext addrNTN + -> Channel m bLF + -> m ((), Maybe bLF) + aLeiosFetchServer version ResponderContext { rcConnectionId = them } channel = do + labelThisThread "LeiosFetchServer" + runPeerWithLimits + (TraceLabelPeer them `contramap` tLeiosFetchTracer) + (cLeiosFetchCodec (mkCodecs version)) + blLeiosFetch + timeLimitsLeiosFetch + channel + $ hLeiosFetchServer version them + {------------------------------------------------------------------------------- Projections from 'Apps' -------------------------------------------------------------------------------} @@ -948,7 +1032,7 @@ initiator :: MiniProtocolParameters -> NodeToNodeVersion -> NodeToNodeVersionData - -> Apps m addr b b b b b b a c + -> Apps m addr b b b b b b b a c -> OuroborosBundleWithExpandedCtx 'Mux.InitiatorMode addr b m a Void initiator miniProtocolParameters version versionData Apps {..} = nodeToNodeProtocols @@ -982,13 +1066,13 @@ initiator miniProtocolParameters version versionData Apps {..} = ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) } -{- , ON.MiniProtocol { + , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosFetchProtocolLimits, - ON.miniProtocolRun = InitiatorProtocolOnly (MiniProtocolCb undefined) + ON.miniProtocolRun = InitiatorProtocolOnly + (MiniProtocolCb (\initiatorCtx -> aLeiosFetchClient version initiatorCtx)) } --} ] } @@ -1001,7 +1085,7 @@ initiatorAndResponder :: MiniProtocolParameters -> NodeToNodeVersion -> NodeToNodeVersionData - -> Apps m addr b b b b b b a c + -> Apps m addr b b b b b b b a c -> OuroborosBundleWithExpandedCtx 'Mux.InitiatorResponderMode addr b m a c initiatorAndResponder miniProtocolParameters version versionData Apps {..} = nodeToNodeProtocols @@ -1041,13 +1125,14 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = (MiniProtocolCb (\initiatorCtx -> aLeiosNotifyClient version initiatorCtx)) (MiniProtocolCb (\responderCtx -> aLeiosNotifyServer version responderCtx)) } -{- , ON.MiniProtocol { + , ON.MiniProtocol { ON.miniProtocolNum = leiosFetchMiniProtocolNum, ON.miniProtocolStart = ON.StartOnDemand, ON.miniProtocolLimits = leiosFetchProtocolLimits, - ON.miniProtocolRun = InitiatorAndResponderProtocol (MiniProtocolCb undefined) (MiniProtocolCb undefined) + ON.miniProtocolRun = InitiatorAndResponderProtocol + (MiniProtocolCb (\initiatorCtx -> aLeiosFetchClient version initiatorCtx)) + (MiniProtocolCb (\responderCtx -> aLeiosFetchServer version responderCtx)) } --} ] } diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs index 6e1c2de8c8..01f527fe2b 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs @@ -626,6 +626,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} = ByteString ByteString ByteString + ByteString NodeToNodeInitiatorResult () mkNodeToNodeApps nodeKernelArgs nodeKernel peerMetrics encAddrNTN decAddrNTN version = @@ -666,6 +667,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} = ByteString ByteString ByteString + ByteString NodeToNodeInitiatorResult () ) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 058ff4d0a1..c3616adca1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} @@ -15,40 +16,45 @@ module LeiosDemoOnlyTestFetch ( LeiosFetch (..) , SingLeiosFetch (..) , Message (..) + , leiosFetchMiniProtocolNum + -- * , byteLimitsLeiosFetch , timeLimitsLeiosFetch , codecLeiosFetch , codecLeiosFetchId - , leiosFetchMiniProtocolNum + -- * + , LeiosFetchClientPeer + , LeiosFetchServerPeer + , leiosFetchClientPeer + , leiosFetchServerPeer ) where import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR -import Control.DeepSeq (NFData (..)) -import Control.Monad.Class.MonadST -import Data.ByteString.Lazy (ByteString) -import Data.Kind (Type) -import Data.Singletons -import Data.Word (Word16, Word64) +import Control.DeepSeq (NFData (..)) +import Control.Monad.Class.MonadST +import Data.ByteString.Lazy (ByteString) +import Data.Functor ((<&>)) +import Data.Kind (Type) +import Data.Singletons +import Data.Word (Word16, Word64) import qualified Network.Mux.Types as Mux -import Network.TypedProtocol.Codec.CBOR -import Network.TypedProtocol.Core -import Ouroboros.Network.Protocol.Limits -import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) -import Text.Printf +import Network.TypedProtocol.Codec.CBOR +import Network.TypedProtocol.Core +import Network.TypedProtocol.Peer +import Ouroboros.Network.Protocol.Limits +import Ouroboros.Network.Util.ShowProxy (ShowProxy (..)) +import Text.Printf ----- leiosFetchMiniProtocolNum :: Mux.MiniProtocolNum leiosFetchMiniProtocolNum = Mux.MiniProtocolNum 19 -type LeiosFetch :: Type -> Type -> Type -> Type -data LeiosFetch point eb tx where - StIdle :: LeiosFetch point eb tx - StBlock :: LeiosFetch point eb tx - StBlockTxs :: LeiosFetch point eb tx - StDone :: LeiosFetch point eb tx +data LeiosFetch point eb tx = StIdle | StBusy (LeiosFetchBusy point eb tx) | StDone + +data LeiosFetchBusy point eb tx = StBlock | StBlockTxs instance ( ShowProxy point , ShowProxy eb @@ -65,13 +71,13 @@ instance ( ShowProxy point showProxy (Proxy :: Proxy tx) ] -instance ShowProxy (StIdle :: LeiosFetch point eb tx) where +instance ShowProxy (StIdle :: LeiosFetch point eb tx) where showProxy _ = "StIdle" -instance ShowProxy (StBlock :: LeiosFetch point eb tx) where - showProxy _ = "StBlock" -instance ShowProxy (StBlockTxs :: LeiosFetch point eb tx) where - showProxy _ = "StBlockTxs" -instance ShowProxy (StDone :: LeiosFetch point eb tx) where +instance ShowProxy (StBusy StBlock :: LeiosFetch point eb tx) where + showProxy _ = "(StBusy StBlock)" +instance ShowProxy (StBusy StBlockTxs :: LeiosFetch point eb tx) where + showProxy _ = "(StBusy StBlockTxs)" +instance ShowProxy (StDone :: LeiosFetch point eb tx) where showProxy _ = "StDone" type SingLeiosFetch @@ -79,16 +85,16 @@ type SingLeiosFetch -> Type data SingLeiosFetch st where SingIdle :: SingLeiosFetch StIdle - SingBlock :: SingLeiosFetch StBlock - SingBlockTxs :: SingLeiosFetch StBlockTxs + SingBlock :: SingLeiosFetch (StBusy StBlock) + SingBlockTxs :: SingLeiosFetch (StBusy StBlockTxs) SingDone :: SingLeiosFetch StDone deriving instance Show (SingLeiosFetch st) -instance StateTokenI StIdle where stateToken = SingIdle -instance StateTokenI StBlock where stateToken = SingBlock -instance StateTokenI StBlockTxs where stateToken = SingBlockTxs -instance StateTokenI StDone where stateToken = SingDone +instance StateTokenI StIdle where stateToken = SingIdle +instance StateTokenI (StBusy StBlock) where stateToken = SingBlock +instance StateTokenI (StBusy StBlockTxs) where stateToken = SingBlockTxs +instance StateTokenI StDone where stateToken = SingDone ----- @@ -96,18 +102,18 @@ instance Protocol (LeiosFetch point eb tx) where data Message (LeiosFetch point eb tx) from to where MsgLeiosBlockRequest :: !point - -> Message (LeiosFetch point eb tx) StIdle StBlock + -> Message (LeiosFetch point eb tx) StIdle (StBusy StBlock) MsgLeiosBlock :: !eb - -> Message (LeiosFetch point eb tx) StBlock StIdle + -> Message (LeiosFetch point eb tx) (StBusy StBlock) StIdle MsgLeiosBlockTxsRequest :: !point -> [(Word16, Word64)] - -> Message (LeiosFetch point eb tx) StIdle StBlockTxs + -> Message (LeiosFetch point eb tx) StIdle (StBusy StBlockTxs) MsgLeiosBlockTxs :: ![tx] - -> Message (LeiosFetch point eb tx) StBlockTxs StIdle + -> Message (LeiosFetch point eb tx) (StBusy StBlockTxs) StIdle -- MsgLeiosVotesRequest -- MsgLeiosVoteDelivery @@ -119,10 +125,10 @@ instance Protocol (LeiosFetch point eb tx) where MsgDone :: Message (LeiosFetch point eb tx) StIdle StDone - type StateAgency StIdle = ClientAgency - type StateAgency StBlock = ServerAgency - type StateAgency StBlockTxs = ServerAgency - type StateAgency StDone = NobodyAgency + type StateAgency StIdle = ClientAgency + type StateAgency (StBusy StBlock) = ServerAgency + type StateAgency (StBusy StBlockTxs) = ServerAgency + type StateAgency StDone = NobodyAgency type StateToken = SingLeiosFetch @@ -347,3 +353,79 @@ decodeBitmaps = [] reverse ((,) <$> CBOR.decodeWord16 <*> CBOR.decodeWord64) + +----- + +data SomeTask point eb tx m = + forall st'. + MkSomeTask + (Message (LeiosFetch point eb tx) StIdle (StBusy st')) + (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ()) + +type LeiosFetchClientPeer point eb tx m a = + Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a + +leiosFetchClientPeer :: + forall m point eb tx a. + Monad m + => + m (Either a (SomeTask point eb tx m)) + -> + Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a +leiosFetchClientPeer checkDone = + go + where + go :: Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a + go = Effect $ checkDone <&> \case + Left x -> + Yield ReflClientAgency MsgDone + $ Done ReflNobodyAgency x + Right (MkSomeTask req k) -> case req of + MsgLeiosBlockRequest{} -> do + Yield ReflClientAgency req + $ Await ReflServerAgency $ \rsp -> case rsp of + MsgLeiosBlock{} -> react $ k rsp + MsgLeiosBlockTxsRequest{} -> do + Yield ReflClientAgency req + $ Await ReflServerAgency $ \rsp -> case rsp of + MsgLeiosBlockTxs{} -> react $ k rsp + + react action = Effect $ fmap (\() -> go) action + +----- + +type LeiosFetchServerPeer point eb tx m a = + Peer (LeiosFetch point eb tx) AsServer NonPipelined StIdle m () + +newtype RequestHandler point eb tx m = MkRequestHandler ( + forall st'. + Message (LeiosFetch point eb tx) StIdle (StBusy st') + -> + m (Message (LeiosFetch point eb tx) (StBusy st') StIdle) + ) + +leiosFetchServerPeer :: + forall m point eb tx. + Monad m + => + m (RequestHandler point eb tx m) + -> + Peer (LeiosFetch point eb tx) AsServer NonPipelined StIdle m () +leiosFetchServerPeer handler = + go + where + go :: Peer (LeiosFetch point eb tx) AsServer NonPipelined StIdle m () + go = Await ReflClientAgency $ \req -> case req of + MsgDone -> Done ReflNobodyAgency () + MsgLeiosBlockRequest{} -> Effect $ do + MkRequestHandler f <- handler + rsp <- f req + pure + $ Yield ReflServerAgency rsp + $ go + MsgLeiosBlockTxsRequest{} -> Effect $ do + MkRequestHandler f <- handler + rsp <- f req + pure + $ Yield ReflServerAgency rsp + $ go diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index f76ff1b824..44c76b0e11 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -3,7 +3,9 @@ module LeiosDemoTypes (module LeiosDemoTypes) where import Cardano.Binary (enforceSize) import Cardano.Slotting.Slot (SlotNo) import Codec.CBOR.Decoding (Decoder) -import Codec.CBOR.Encoding (Encoding, encodeListLen) +import qualified Codec.CBOR.Decoding as CBOR +import Codec.CBOR.Encoding (Encoding) +import qualified Codec.CBOR.Encoding as CBOR import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) import Data.ByteString (ByteString) @@ -31,19 +33,18 @@ newtype EbHash = MkEbHash ByteString deriving (Eq, Ord, Show) newtype TxHash = MkTxHash ByteString - deriving (Eq, Ord) + deriving (Eq, Ord, Show) data LeiosPoint = MkLeiosPoint SlotNo EbHash deriving (Show) -instance ShowProxy LeiosPoint where - showProxy _ = "LeiosPoint" +instance ShowProxy LeiosPoint where showProxy _ = "LeiosPoint" encodeLeiosPoint :: LeiosPoint -> Encoding encodeLeiosPoint (MkLeiosPoint ebSlot (MkEbHash ebHash)) = - encodeListLen 2 + CBOR.encodeListLen 2 <> encode ebSlot - <> encode ebHash + <> CBOR.encodeBytes ebHash decodeLeiosPoint :: Decoder s LeiosPoint decodeLeiosPoint = do @@ -164,3 +165,40 @@ data LeiosToCopy = MkLeiosToCopy { emptyLeiosToCopy :: LeiosToCopy emptyLeiosToCopy = MkLeiosToCopy Map.empty 0 0 + +----- + +newtype LeiosTx = MkLeiosTx ByteString + deriving (Show) + +instance ShowProxy LeiosTx where showProxy _ = "LeiosTx" + +encodeLeiosTx :: LeiosTx -> Encoding +encodeLeiosTx (MkLeiosTx bytes) = CBOR.encodeBytes bytes + +decodeLeiosTx :: Decoder s LeiosTx +decodeLeiosTx = MkLeiosTx <$> CBOR.decodeBytes + +data LeiosEb = MkLeiosEb !(V.Vector (TxHash, BytesSize)) + deriving (Show) + +instance ShowProxy LeiosEb where showProxy _ = "LeiosEb" + +encodeLeiosEb :: LeiosEb -> Encoding +encodeLeiosEb (MkLeiosEb v) = + V.foldl + (\acc (MkTxHash bytes, txBytesSize) -> + acc <> CBOR.encodeBytes bytes <> CBOR.encodeWord32 txBytesSize + ) + (CBOR.encodeMapLen $ fromIntegral $ V.length v) + v + +decodeLeiosEb :: Decoder s LeiosEb +decodeLeiosEb = do + n <- CBOR.decodeMapLen + -- TODO does V.generateM allocate exacly one buffer, via the hint? + -- + -- If not, we could do so manually by relying on the fact that Decoder is + -- ultimate in ST. + fmap MkLeiosEb $ V.generateM n $ \_i -> do + (,) <$> (fmap MkTxHash CBOR.decodeBytes) <*> CBOR.decodeWord32 From 4238e128e9e72c1275242056c5e7683fe75dcb0f Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 13:29:16 -0700 Subject: [PATCH 080/119] fixup leiosdemo202510: LeiosNotify --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 2 +- .../LeiosDemoOnlyTestNotify.hs | 70 ++++++++++++------- 2 files changed, 46 insertions(+), 26 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 2fbea19c1c..fbc045d770 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -307,7 +307,7 @@ mkHandlers (atomically controlMessageSTM <&> \case Terminate -> Left () _ -> Right 300 {- TODO magic number -}) - (\case + (pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index 806736d988..bd88e93afa 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -17,6 +17,7 @@ module LeiosDemoOnlyTestNotify ( LeiosNotify (..) , SingLeiosNotify (..) , Message (..) + , leiosNotifyMiniProtocolNum -- * , byteLimitsLeiosNotify , timeLimitsLeiosNotify @@ -25,7 +26,6 @@ module LeiosDemoOnlyTestNotify -- * , LeiosNotifyClientPeerPipelined , LeiosNotifyServerPeer - , leiosNotifyMiniProtocolNum , leiosNotifyClientPeer , leiosNotifyClientPeerPipelined , leiosNotifyServerPeer @@ -34,7 +34,10 @@ module LeiosDemoOnlyTestNotify import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR +import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) +import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.DeepSeq (NFData (..)) +import Control.Monad (when) import Control.Monad.Class.MonadST import Data.ByteString.Lazy (ByteString) import Data.Functor ((<&>)) @@ -355,53 +358,70 @@ leiosNotifyServerPeer handler = ----- --- | Merely an abbrevation local to this module +-- | Merely an abbreviation local to this module type X point announcement m a n = - Peer (LeiosNotify point announcement) AsClient (Pipelined n (C m)) StIdle m a + Peer (LeiosNotify point announcement) AsClient (Pipelined n C) StIdle m a type LeiosNotifyClientPeerPipelined point announcement m a = PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a -newtype C m = MkC (m ()) +data C = MkC leiosNotifyClientPeerPipelined :: - forall m announcement point a. - Monad m + forall m point announcement a. + MonadMVar m => m (Either a Int) -- ^ either the return value or else the current max pipelining depth -> - (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) + m (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) -> PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a -leiosNotifyClientPeerPipelined checkDone handler = - PeerPipelined (go Zero) +leiosNotifyClientPeerPipelined checkDone k0 = + PeerPipelined $ Effect $ do + stop <- MVar.newEmptyMVar -- would be IORef if io-classes had it + pure $ go stop Zero where - go :: Nat n -> X point announcement m a n - go !n = Effect $ checkDone <&> \case - Left x -> drainThePipe x n + go :: MVar m () -> Nat n -> X point announcement m a n + go stop !n = Effect $ checkDone <&> \case + Left x -> Effect $ do + MVar.putMVar stop () + pure $ drainThePipe x n Right maxDepth -> case n of - Zero -> sendAnother n + Zero -> sendAnother stop n Succ m -> Collect - (if natToInt n >= maxDepth then Nothing else Just $ sendAnother n) - (\(MkC action) -> Effect $ do action; pure $ go m) + (if natToInt n >= maxDepth then Nothing else Just $ sendAnother stop n) + (\MkC -> go stop m) - sendAnother :: Nat n -> X point announcement m a n - sendAnother !n = + sendAnother :: MVar m () -> Nat n -> X point announcement m a n + sendAnother stop !n = YieldPipelined ReflClientAgency MsgLeiosNotificationRequestNext - receiver - (go $ Succ n) + (receiver stop) + (go stop $ Succ n) - receiver :: Receiver (LeiosNotify point announcement) AsClient StBusy StIdle m (C m) - receiver = + receiver :: MVar m () -> Receiver (LeiosNotify point announcement) AsClient StBusy StIdle m C + receiver stop = ReceiverAwait ReflServerAgency $ \msg -> case msg of - MsgLeiosBlockAnnouncement{} -> ReceiverDone $ MkC $ handler msg - MsgLeiosBlockOffer{} -> ReceiverDone $ MkC $ handler msg - MsgLeiosBlockTxsOffer{} -> ReceiverDone $ MkC $ handler msg + MsgLeiosBlockAnnouncement{} -> handler stop k0 msg + MsgLeiosBlockOffer{} -> handler stop k0 msg + MsgLeiosBlockTxsOffer{} -> handler stop k0 msg + + handler :: + MVar m () + -> + m (msg -> m ()) + -> + msg + -> + Receiver (LeiosNotify point announcement) AsClient StIdle StIdle m C + handler stop k x = ReceiverEffect $ do + b <- MVar.isEmptyMVar stop + when b $ k >>= ($ x) + pure $ ReceiverDone MkC drainThePipe :: a -> Nat n -> X point announcement m a n drainThePipe x = \case @@ -411,4 +431,4 @@ leiosNotifyClientPeerPipelined checkDone handler = Succ m -> Collect Nothing - (\(MkC action) -> Effect $ do action; pure $ drainThePipe x m) + (\MkC -> drainThePipe x m) From dc09aab4b382280c5d96d87cef9cf7e11be33cde Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 13:31:34 -0700 Subject: [PATCH 081/119] leiosdemo202510: add generalized LeiosFetch pipelined client --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 8 +- .../LeiosDemoOnlyTestFetch.hs | 125 ++++++++++++++++-- 2 files changed, 117 insertions(+), 16 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index fbc045d770..ae7619eb6d 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -230,7 +230,7 @@ data Handlers m addr blk = Handlers { :: NodeToNodeVersion -> ControlMessageSTM m -> ConnectionId addr - -> LeiosFetchClientPeer LeiosPoint LeiosEb LeiosTx m () + -> LeiosFetchClientPeerPipelined LeiosPoint LeiosEb LeiosTx m () , hLeiosFetchServer :: NodeToNodeVersion @@ -345,8 +345,8 @@ mkHandlers leiosNotifyServerPeer (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO , hLeiosFetchClient = \_version controlMessageSTM _peer -> - leiosFetchClientPeer - (atomically $ controlMessageSTM >>= \case + leiosFetchClientPeerPipelined + (pure $ Left $ atomically $ controlMessageSTM >>= \case Terminate -> pure $ Left () _ -> retry ) -- TODO @@ -994,7 +994,7 @@ mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucke eicControlMessage = controlMessageSTM } channel = do labelThisThread "LeiosFetchClient" - ((), trailing) <- runPeerWithLimits + ((), trailing) <- runPipelinedPeerWithLimits (TraceLabelPeer them `contramap` tLeiosFetchTracer) (cLeiosFetchCodec (mkCodecs version)) blLeiosFetch diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index c3616adca1..02831d61ab 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -24,15 +24,20 @@ module LeiosDemoOnlyTestFetch , codecLeiosFetchId -- * , LeiosFetchClientPeer + , LeiosFetchClientPeerPipelined , LeiosFetchServerPeer , leiosFetchClientPeer + , leiosFetchClientPeerPipelined , leiosFetchServerPeer ) where import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR +import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) +import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.DeepSeq (NFData (..)) +import Control.Monad (when) import Control.Monad.Class.MonadST import Data.ByteString.Lazy (ByteString) import Data.Functor ((<&>)) @@ -125,10 +130,9 @@ instance Protocol (LeiosFetch point eb tx) where MsgDone :: Message (LeiosFetch point eb tx) StIdle StDone - type StateAgency StIdle = ClientAgency - type StateAgency (StBusy StBlock) = ServerAgency - type StateAgency (StBusy StBlockTxs) = ServerAgency - type StateAgency StDone = NobodyAgency + type StateAgency StIdle = ClientAgency + type StateAgency (StBusy st) = ServerAgency + type StateAgency StDone = NobodyAgency type StateToken = SingLeiosFetch @@ -356,11 +360,13 @@ decodeBitmaps = ----- -data SomeTask point eb tx m = +data SomeJob point eb tx m = forall st'. - MkSomeTask - (Message (LeiosFetch point eb tx) StIdle (StBusy st')) - (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ()) + StateTokenI (StBusy st') + => + MkSomeJob + (Message (LeiosFetch point eb tx) StIdle (StBusy st')) + (m (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ())) type LeiosFetchClientPeer point eb tx m a = Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a @@ -369,7 +375,7 @@ leiosFetchClientPeer :: forall m point eb tx a. Monad m => - m (Either a (SomeTask point eb tx m)) + m (Either a (SomeJob point eb tx m)) -> Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a leiosFetchClientPeer checkDone = @@ -380,15 +386,15 @@ leiosFetchClientPeer checkDone = Left x -> Yield ReflClientAgency MsgDone $ Done ReflNobodyAgency x - Right (MkSomeTask req k) -> case req of + Right (MkSomeJob req k) -> case req of MsgLeiosBlockRequest{} -> do Yield ReflClientAgency req $ Await ReflServerAgency $ \rsp -> case rsp of - MsgLeiosBlock{} -> react $ k rsp + MsgLeiosBlock{} -> react $ k >>= ($ rsp) MsgLeiosBlockTxsRequest{} -> do Yield ReflClientAgency req $ Await ReflServerAgency $ \rsp -> case rsp of - MsgLeiosBlockTxs{} -> react $ k rsp + MsgLeiosBlockTxs{} -> react $ k >>= ($ rsp) react action = Effect $ fmap (\() -> go) action @@ -429,3 +435,98 @@ leiosFetchServerPeer handler = pure $ Yield ReflServerAgency rsp $ go + +----- + +-- | Merely an abbreviation local to this module +type X point eb tx m a n = + Peer (LeiosFetch point eb tx) AsClient (Pipelined n C) StIdle m a + +type LeiosFetchClientPeerPipelined point eb tx m a = + PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a + +data C = MkC + +leiosFetchClientPeerPipelined :: + forall m point eb tx a. + MonadMVar m + => + m (Either (m (Either a (SomeJob point eb tx m))) (Either a (SomeJob point eb tx m))) + -- ^ either the return value or the next job, or a blocking request for those two + -> + PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a +leiosFetchClientPeerPipelined tryNext = + PeerPipelined $ Effect $ do + stop <- MVar.newEmptyMVar -- would be IORef if io-classes had it + pure $ go1 stop Zero + where + go1 :: MVar m () -> Nat n -> X point eb tx m a n + go1 stop !n = + Effect $ tryNext >>= \case + -- no next instruction yet + Left next -> + case n of + Zero -> next <&> go2 stop Zero + Succ m -> + pure + $ Collect + Nothing + (\MkC -> go1 stop m) + Right x -> pure $ go2 stop n x + + go2 :: MVar m () -> Nat n -> Either a (SomeJob point eb tx m) -> X point eb tx m a n + go2 stop !n = \case + Left x -> Effect $ do + MVar.putMVar stop () + pure $ drainThePipe x n + Right job -> + case n of + Zero -> send stop n job + Succ m -> + Collect + (Just $ send stop n job) + (\MkC -> go1 stop m) + + send :: MVar m () -> Nat n -> SomeJob point eb tx m -> X point eb tx m a n + send stop !n (MkSomeJob req k) = + YieldPipelined + ReflClientAgency + req + (receiver stop k) + (go1 stop $ Succ n) + + receiver :: + StateTokenI (StBusy st') + => + MVar m () + -> + m (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ()) + -> + Receiver (LeiosFetch point eb tx) AsClient (StBusy st') StIdle m C + receiver stop k = + ReceiverAwait ReflServerAgency $ \msg -> case msg of + MsgLeiosBlock{} -> handler stop k msg + MsgLeiosBlockTxs{} -> handler stop k msg + + handler :: + MVar m () + -> + m (msg -> m ()) + -> + msg + -> + Receiver (LeiosFetch point eb tx) AsClient StIdle StIdle m C + handler stop k x = ReceiverEffect $ do + b <- MVar.isEmptyMVar stop + when b $ k >>= ($ x) + pure $ ReceiverDone MkC + + drainThePipe :: a -> Nat n -> X point eb tx m a n + drainThePipe x = \case + Zero -> + Yield ReflClientAgency MsgDone + $ Done ReflNobodyAgency x + Succ m -> + Collect + Nothing + (\MkC -> drainThePipe x m) From 15052f5a8e032551a8e1d508edaf7ccd2e5e7241 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 13:36:15 -0700 Subject: [PATCH 082/119] leiosdemo202510: switch requestsToSend to TVar, for convenience --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 18 +++++++++--------- .../Ouroboros/Consensus/NodeKernel.hs | 8 ++++---- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 10 +++++++--- 3 files changed, 20 insertions(+), 16 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index ae7619eb6d..aeefeba191 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -320,23 +320,23 @@ mkHandlers Map.insert ebId ebBytesSize (Leios.missingEbBodies ebBodies2) } pure (ebBodies3, ebId) - peerMVars <- do - peersMVars <- MVar.readMVar getLeiosPeersMVars - case Map.lookup (Leios.MkPeerId peer) peersMVars of + peerVars <- do + peersVars <- MVar.readMVar getLeiosPeersVars + case Map.lookup (Leios.MkPeerId peer) peersVars of Nothing -> error "TODO" Just x -> pure x - MVar.modifyMVar_ (Leios.offerings peerMVars) $ \(offers1, offers2) -> do + MVar.modifyMVar_ (Leios.offerings peerVars) $ \(offers1, offers2) -> do let !offers1' = Set.insert ebId offers1 pure (offers1', offers2) void $ MVar.tryPutMVar getLeiosReady () MsgLeiosBlockTxsOffer p -> do ebId <- Leios.ebIdFromPointM getLeiosEbBodies p - peerMVars <- do - peersMVars <- MVar.readMVar getLeiosPeersMVars - case Map.lookup (Leios.MkPeerId peer) peersMVars of + peerVars <- do + peersVars <- MVar.readMVar getLeiosPeersVars + case Map.lookup (Leios.MkPeerId peer) peersVars of Nothing -> error "TODO" Just x -> pure x - MVar.modifyMVar_ (Leios.offerings peerMVars) $ \(offers1, offers2) -> do + MVar.modifyMVar_ (Leios.offerings peerVars) $ \(offers1, offers2) -> do let !offers2' = Set.insert ebId offers2 pure (offers1, offers2') void $ MVar.tryPutMVar getLeiosReady () @@ -356,7 +356,7 @@ mkHandlers } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel - NodeKernel {getLeiosPeersMVars, getLeiosEbBodies, getLeiosReady} = nodeKernel + NodeKernel {getLeiosPeersVars, getLeiosEbBodies, getLeiosReady} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 0e9ad91244..e52a8abcd9 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -193,8 +193,8 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- TODO this could all use TVars, but I'm curious whether MVars are a -- noticeably awkward fit for this logic. - -- See 'LeiosPeerMVars' for the write patterns - , getLeiosPeersMVars :: MVar m (Map (PeerId (ConnectionId addrNTN)) (LeiosPeerMVars m)) + -- See 'LeiosPeerVars' for the write patterns + , getLeiosPeersVars :: MVar m (Map (PeerId (ConnectionId addrNTN)) (LeiosPeerVars m)) -- written to by the LeiosNotify&LeiosFetch clients (TODO and by -- eviction) , getLeiosEbBodies :: MVar m LeiosEbBodies @@ -362,7 +362,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers fetchClientRegistry blockFetchConfiguration - getLeiosPeersMVars <- MVar.newMVar Map.empty + getLeiosPeersVars <- MVar.newMVar Map.empty getLeiosEbBodies <- MVar.newMVar emptyLeiosEbBodies getLeiosOutstanding <- MVar.newMVar emptyLeiosOutstanding getLeiosToCopy <- MVar.newMVar emptyLeiosToCopy @@ -385,7 +385,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getDiffusionPipeliningSupport , getBlockchainTime = btime - , getLeiosPeersMVars + , getLeiosPeersVars , getLeiosEbBodies , getLeiosOutstanding , getLeiosToCopy diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 44c76b0e11..29033e7c09 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -8,6 +8,7 @@ import Codec.CBOR.Encoding (Encoding) import qualified Codec.CBOR.Encoding as CBOR import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) +import Control.Concurrent.Class.MonadSTM (TVar) import Data.ByteString (ByteString) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap @@ -85,11 +86,11 @@ data LeiosBlockTxsRequest = -- patterns of access to the "Ouroboros.Consensus.NodeKernel"'s shared state. -- -data LeiosPeerMVars m = MkLeiosPeerMVars { +data LeiosPeerVars m = MkLeiosPeerVars { -- written to only by the LeiosNotify client (TODO and eviction) offerings :: !(MVar m (Set EbId, Set EbId)) , - -- written to by the fetch logic and the LeiosFetch client + -- | written to by the fetch logic and the LeiosFetch client -- -- These are the requests the fetch logic assumes will be sent, but have -- not already been sent. @@ -100,7 +101,10 @@ data LeiosPeerMVars m = MkLeiosPeerMVars { -- -- Note that @requestedPerPeer@ is the list maintained per client, -- whereas this list is not present in the model exe. - requestsToSend :: !(MVar m (Seq LeiosFetchRequest)) + -- + -- This is a 'TVar' so that the LeiosFetch client can wait on either it or + -- the Diffusion Layer's control message to be actionable. + requestsToSend :: !(TVar m (Seq LeiosFetchRequest)) } data LeiosEbBodies = MkLeiosEbBodies { From eff731f4db1fe19a1201fd3223e910f26f328ea7 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sat, 25 Oct 2025 13:51:57 -0700 Subject: [PATCH 083/119] leiosdemo202510: use MutVar instead of MVar for drainThePipe --- .../LeiosDemoOnlyTestFetch.hs | 29 ++++++++++--------- .../LeiosDemoOnlyTestNotify.hs | 27 +++++++++-------- 2 files changed, 31 insertions(+), 25 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 02831d61ab..4e4a3d5e1f 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -34,14 +34,14 @@ module LeiosDemoOnlyTestFetch import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR -import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) -import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.DeepSeq (NFData (..)) -import Control.Monad (when) import Control.Monad.Class.MonadST +import Control.Monad.Primitive (PrimMonad, PrimState) import Data.ByteString.Lazy (ByteString) import Data.Functor ((<&>)) import Data.Kind (Type) +import Data.Primitive.MutVar (MutVar) +import qualified Data.Primitive.MutVar as Prim import Data.Singletons import Data.Word (Word16, Word64) import qualified Network.Mux.Types as Mux @@ -447,9 +447,11 @@ type LeiosFetchClientPeerPipelined point eb tx m a = data C = MkC +data WhetherDraining = AlreadyDraining | NotYetDraining + leiosFetchClientPeerPipelined :: forall m point eb tx a. - MonadMVar m + PrimMonad m => m (Either (m (Either a (SomeJob point eb tx m))) (Either a (SomeJob point eb tx m))) -- ^ either the return value or the next job, or a blocking request for those two @@ -457,10 +459,10 @@ leiosFetchClientPeerPipelined :: PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a leiosFetchClientPeerPipelined tryNext = PeerPipelined $ Effect $ do - stop <- MVar.newEmptyMVar -- would be IORef if io-classes had it + stop <- Prim.newMutVar NotYetDraining pure $ go1 stop Zero where - go1 :: MVar m () -> Nat n -> X point eb tx m a n + go1 :: MutVar (PrimState m) WhetherDraining -> Nat n -> X point eb tx m a n go1 stop !n = Effect $ tryNext >>= \case -- no next instruction yet @@ -474,10 +476,10 @@ leiosFetchClientPeerPipelined tryNext = (\MkC -> go1 stop m) Right x -> pure $ go2 stop n x - go2 :: MVar m () -> Nat n -> Either a (SomeJob point eb tx m) -> X point eb tx m a n + go2 :: MutVar (PrimState m) WhetherDraining -> Nat n -> Either a (SomeJob point eb tx m) -> X point eb tx m a n go2 stop !n = \case Left x -> Effect $ do - MVar.putMVar stop () + Prim.writeMutVar stop AlreadyDraining pure $ drainThePipe x n Right job -> case n of @@ -487,7 +489,7 @@ leiosFetchClientPeerPipelined tryNext = (Just $ send stop n job) (\MkC -> go1 stop m) - send :: MVar m () -> Nat n -> SomeJob point eb tx m -> X point eb tx m a n + send :: MutVar (PrimState m) WhetherDraining -> Nat n -> SomeJob point eb tx m -> X point eb tx m a n send stop !n (MkSomeJob req k) = YieldPipelined ReflClientAgency @@ -498,7 +500,7 @@ leiosFetchClientPeerPipelined tryNext = receiver :: StateTokenI (StBusy st') => - MVar m () + MutVar (PrimState m) WhetherDraining -> m (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ()) -> @@ -509,7 +511,7 @@ leiosFetchClientPeerPipelined tryNext = MsgLeiosBlockTxs{} -> handler stop k msg handler :: - MVar m () + MutVar (PrimState m) WhetherDraining -> m (msg -> m ()) -> @@ -517,8 +519,9 @@ leiosFetchClientPeerPipelined tryNext = -> Receiver (LeiosFetch point eb tx) AsClient StIdle StIdle m C handler stop k x = ReceiverEffect $ do - b <- MVar.isEmptyMVar stop - when b $ k >>= ($ x) + Prim.readMutVar stop >>= \case + AlreadyDraining -> pure () + NotYetDraining -> k >>= ($ x) pure $ ReceiverDone MkC drainThePipe :: a -> Nat n -> X point eb tx m a n diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index bd88e93afa..8d42ebd244 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -34,14 +34,14 @@ module LeiosDemoOnlyTestNotify import qualified Codec.CBOR.Decoding as CBOR import qualified Codec.CBOR.Encoding as CBOR import qualified Codec.CBOR.Read as CBOR -import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) -import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.DeepSeq (NFData (..)) -import Control.Monad (when) import Control.Monad.Class.MonadST +import Control.Monad.Primitive (PrimMonad, PrimState) import Data.ByteString.Lazy (ByteString) import Data.Functor ((<&>)) import Data.Kind (Type) +import Data.Primitive.MutVar (MutVar) +import qualified Data.Primitive.MutVar as Prim import Data.Singletons import Data.Word (Word32) import qualified Network.Mux.Types as Mux @@ -367,9 +367,11 @@ type LeiosNotifyClientPeerPipelined point announcement m a = data C = MkC +data WhetherDraining = AlreadyDraining | NotYetDraining + leiosNotifyClientPeerPipelined :: forall m point announcement a. - MonadMVar m + PrimMonad m => m (Either a Int) -- ^ either the return value or else the current max pipelining depth @@ -379,13 +381,13 @@ leiosNotifyClientPeerPipelined :: PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a leiosNotifyClientPeerPipelined checkDone k0 = PeerPipelined $ Effect $ do - stop <- MVar.newEmptyMVar -- would be IORef if io-classes had it + stop <- Prim.newMutVar NotYetDraining pure $ go stop Zero where - go :: MVar m () -> Nat n -> X point announcement m a n + go :: MutVar (PrimState m) WhetherDraining -> Nat n -> X point announcement m a n go stop !n = Effect $ checkDone <&> \case Left x -> Effect $ do - MVar.putMVar stop () + Prim.writeMutVar stop AlreadyDraining pure $ drainThePipe x n Right maxDepth -> case n of @@ -395,7 +397,7 @@ leiosNotifyClientPeerPipelined checkDone k0 = (if natToInt n >= maxDepth then Nothing else Just $ sendAnother stop n) (\MkC -> go stop m) - sendAnother :: MVar m () -> Nat n -> X point announcement m a n + sendAnother :: MutVar (PrimState m) WhetherDraining -> Nat n -> X point announcement m a n sendAnother stop !n = YieldPipelined ReflClientAgency @@ -403,7 +405,7 @@ leiosNotifyClientPeerPipelined checkDone k0 = (receiver stop) (go stop $ Succ n) - receiver :: MVar m () -> Receiver (LeiosNotify point announcement) AsClient StBusy StIdle m C + receiver :: MutVar (PrimState m) WhetherDraining -> Receiver (LeiosNotify point announcement) AsClient StBusy StIdle m C receiver stop = ReceiverAwait ReflServerAgency $ \msg -> case msg of MsgLeiosBlockAnnouncement{} -> handler stop k0 msg @@ -411,7 +413,7 @@ leiosNotifyClientPeerPipelined checkDone k0 = MsgLeiosBlockTxsOffer{} -> handler stop k0 msg handler :: - MVar m () + MutVar (PrimState m) WhetherDraining -> m (msg -> m ()) -> @@ -419,8 +421,9 @@ leiosNotifyClientPeerPipelined checkDone k0 = -> Receiver (LeiosNotify point announcement) AsClient StIdle StIdle m C handler stop k x = ReceiverEffect $ do - b <- MVar.isEmptyMVar stop - when b $ k >>= ($ x) + Prim.readMutVar stop >>= \case + AlreadyDraining -> pure () + NotYetDraining -> k >>= ($ x) pure $ ReceiverDone MkC drainThePipe :: a -> Nat n -> X point announcement m a n From c3c90b62f797049487d83528c9e53d9180e89308 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 07:20:36 -0700 Subject: [PATCH 084/119] leiosdemo202510: polishing demo script --- scripts/leios-demo/leios-october-demo.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 714f142327..a7b4e4c0e4 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -177,6 +177,7 @@ IMMDB_SERVER_PID=$! echo "ImmDB server started with PID: $IMMDB_SERVER_PID" read -n 1 -s -r -p "Press any key to stop the spawned processes..." +echo echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." From 1c690a3dfbfef7ae05683421a7a90a618c5eefec Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 09:24:50 -0700 Subject: [PATCH 085/119] leiosdemo202510: add LeiosFetch to immdb-server --- .../app/immdb-server.hs | 15 +- .../ouroboros-consensus-cardano.cabal | 3 +- .../Cardano/Tools/ImmDBServer/Diffusion.hs | 47 +++- .../Tools/ImmDBServer/MiniProtocols.hs | 38 ++-- .../Ouroboros/Consensus/Network/NodeToNode.hs | 2 +- ouroboros-consensus/app/leiosdemo202510.hs | 2 +- ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../src/ouroboros-consensus/LeiosDemoLogic.hs | 215 +++++++++++++++++- .../LeiosDemoOnlyTestFetch.hs | 38 ++-- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 100 ++++++++ scripts/leios-demo/leios-october-demo.sh | 6 + 11 files changed, 418 insertions(+), 49 deletions(-) diff --git a/ouroboros-consensus-cardano/app/immdb-server.hs b/ouroboros-consensus-cardano/app/immdb-server.hs index a26486b7d6..e0817c19a6 100644 --- a/ouroboros-consensus-cardano/app/immdb-server.hs +++ b/ouroboros-consensus-cardano/app/immdb-server.hs @@ -22,12 +22,13 @@ import Options.Applicative (ParserInfo, execParser, fullDesc, help, strOption, value, auto, option) import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..)) import System.Exit (die) +import qualified System.IO as SIO main :: IO () main = withStdTerminalHandles $ do + SIO.hSetBuffering SIO.stdout SIO.LineBuffering cryptoInit - Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosScheduleFile} <- execParser optsParser - + Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosDbFile, leiosScheduleFile} <- execParser optsParser let hints = Socket.defaultHints { addrFlags = [Socket.AI_NUMERICHOST], addrSocketType = Socket.Stream} addrInfo <- do addrInfos <- Socket.getAddrInfo (Just hints) (Just address) (Just port) @@ -46,6 +47,7 @@ main = withStdTerminalHandles $ do (Socket.addrAddress addrInfo) pInfoConfig (mkGetSlotDelay refSlotNr refTimeForRefSlot) + leiosDbFile (leiosSchedule :: ImmDBServer.LeiosSchedule) where -- NB we assume for now the slot duration is 1 second. @@ -78,6 +80,8 @@ data Opts = Opts { , refTimeForRefSlot :: POSIX.POSIXTime -- ^ Reference slot onset. Wallclock time that corresponds to the -- reference slot. + , leiosDbFile :: FilePath + -- ^ SQLite3 file storing the Leios data , leiosScheduleFile :: FilePath -- ^ JSON file encoding the 'ImmDBServer.LeiosSchedule' } @@ -121,9 +125,14 @@ optsParser = , help "UTC time for the reference slot, provided as POSIX seconds (Unix timestamp)" , metavar "POSIX_SECONDS" ] + leiosDbFile <- strOption $ mconcat + [ long "leios-db" + , help "Path to the Leios database" + , metavar "PATH" + ] leiosScheduleFile <- strOption $ mconcat [ long "leios-schedule" , help "Path to json file specifying when to send Leios offers" , metavar "PATH" ] - pure Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosScheduleFile} + pure Opts {immDBDir, port, address, configFile, refSlotNr, refTimeForRefSlot, leiosDbFile, leiosScheduleFile} diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index 492f933958..b60e2b13e7 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -563,6 +563,7 @@ library unstable-cardano-tools compact, containers >=0.5 && <0.8, contra-tracer, + direct-sqlite, directory, dot, filepath, @@ -583,7 +584,6 @@ library unstable-cardano-tools ouroboros-network-framework ^>=0.18, ouroboros-network-protocols, resource-registry, - serialise, singletons, sop-core, sop-extras, @@ -592,6 +592,7 @@ library unstable-cardano-tools text-builder >=1, transformers, transformers-except, + vector, executable db-analyser import: common-lib diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index 100ef64ce2..2e45a8e009 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -3,13 +3,14 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} module Cardano.Tools.ImmDBServer.Diffusion (run, LeiosSchedule (..)) where import qualified Data.Aeson as Aeson -import Cardano.Tools.ImmDBServer.MiniProtocols (immDBServer, LeiosContext (..)) +import qualified Cardano.Tools.ImmDBServer.MiniProtocols as MP import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.ResourceRegistry import Control.Tracer @@ -17,10 +18,13 @@ import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Lazy as BL import Data.Functor.Contravariant ((>$<)) import qualified Data.Map.Strict as Map +import Data.String (fromString) import qualified Data.Text as T import qualified Data.Text.Encoding as T +import qualified Data.Vector.Mutable as MV import Data.Void (Void) import Data.Word (Word32, Word64) +import qualified Database.SQLite3.Direct as DB import GHC.Generics (Generic) import qualified Network.Mux as Mux import Network.Socket (SockAddr (..)) @@ -43,12 +47,14 @@ import Ouroboros.Network.PeerSelection.PeerSharing.Codec (decodeRemoteAddress, encodeRemoteAddress) import qualified Ouroboros.Network.Snocket as Snocket import Ouroboros.Network.Socket (configureSocket) +import qualified System.Directory as Dir import System.Exit (die) import System.FS.API (SomeHasFS (..)) import System.FS.API.Types (MountPoint (MountPoint)) import System.FS.IO (ioHasFS) -import LeiosDemoTypes +import qualified LeiosDemoLogic as LeiosLogic +import qualified LeiosDemoTypes as Leios -- | Glue code for using just the bits from the Diffusion Layer that we need in -- this context. @@ -97,23 +103,40 @@ run :: -> SockAddr -> TopLevelConfig blk -> (Double -> IO DiffTime) + -> FilePath -> LeiosSchedule -> IO Void -run immDBDir sockAddr cfg getSlotDelay leiosSchedule = withRegistry \registry ->do - leiosContext <- do - leiosMailbox <- MVar.newEmptyMVar - pure MkLeiosContext { leiosMailbox } - _threadId <- forkLinkedThread registry "LeiosScheduler" (leiosScheduler getSlotDelay leiosContext leiosSchedule) +run immDBDir sockAddr cfg getSlotDelay leiosDbFile leiosSchedule = withRegistry \registry ->do + let mkLeiosNotifyContext registry' = do + -- each LeiosNotify server calls this when it initializes + leiosMailbox <- MVar.newEmptyMVar + let leiosNotifyContext = MP.MkLeiosNotifyContext { MP.leiosMailbox } + _threadId <- forkLinkedThread registry' "LeiosScheduler" (leiosScheduler getSlotDelay leiosNotifyContext leiosSchedule) + pure leiosNotifyContext + let mkLeiosFetchContext = do + -- each LeiosFetch server calls this when it initializes + leiosEbBuffer <- MV.new Leios.maxEbItems + leiosEbTxsBuffer <- MV.new Leios.maxEbItems + Dir.doesFileExist leiosDbFile >>= \case + False -> die $ "The Leios database must already exist: " <> show leiosDbFile + True -> pure () + leiosDb <- DB.open (fromString leiosDbFile) >>= \case + Left (_err, utf8) -> die $ show utf8 + Right x -> pure $ Leios.leiosDbFromSqliteDirect x + leiosEbBodies <- LeiosLogic.loadEbBodies leiosDb + let leiosFetchContext = LeiosLogic.MkLeiosFetchContext { LeiosLogic.leiosDb, LeiosLogic.leiosEbBodies, LeiosLogic.leiosEbBuffer, LeiosLogic.leiosEbTxsBuffer } + pure $ LeiosLogic.MkSomeLeiosFetchContext leiosFetchContext ImmutableDB.withDB (ImmutableDB.openDB (immDBArgs registry) runWithTempRegistry) - \immDB -> serve sockAddr $ immDBServer + \immDB -> serve sockAddr $ MP.immDBServer codecCfg encodeRemoteAddress decodeRemoteAddress immDB networkMagic (getSlotDelay . fromIntegral . unSlotNo) - leiosContext + mkLeiosNotifyContext + mkLeiosFetchContext where immDBArgs registry = ImmutableDB.defaultArgs { immCheckIntegrity = nodeCheckIntegrity storageCfg @@ -138,7 +161,7 @@ instance Aeson.FromJSON LeiosSchedule leiosScheduler :: (Double -> IO DiffTime) -> - LeiosContext IO + MP.LeiosNotifyContext IO -> LeiosSchedule -> @@ -150,12 +173,12 @@ leiosScheduler getSlotDelay leiosContext = $ Map.fromListWith (++) [ (k, [v]) | (k, v) <- x ] flip mapM_ (Map.toAscList y) $ \(slotDbl, msgs) -> do getSlotDelay slotDbl >>= threadDelay - mapM_ (MVar.putMVar (leiosMailbox leiosContext)) msgs + mapM_ (MVar.putMVar (MP.leiosMailbox leiosContext)) msgs where cnv (ebSlot, ebHashText, !mbEbBytesSize) = do ebHash <- case BS16.decode (T.encodeUtf8 ebHashText) of Left err -> die $ "bad hash in Leios schedule! " ++ T.unpack ebHashText ++ " " ++ err Right y -> pure y - let !rp = MkLeiosPoint (SlotNo ebSlot) (MkEbHash ebHash) + let !rp = Leios.MkLeiosPoint (SlotNo ebSlot) (Leios.MkEbHash ebHash) pure (rp, mbEbBytesSize) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index 6a3d5fbcfd..b1db39b3f5 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} @@ -13,8 +14,8 @@ -- | Implement ChainSync and BlockFetch servers on top of just the immutable DB. module Cardano.Tools.ImmDBServer.MiniProtocols ( + LeiosNotifyContext (..), immDBServer, - LeiosContext (..), ) where import Cardano.Slotting.Slot (WithOrigin (At)) @@ -67,9 +68,10 @@ import Ouroboros.Network.Protocol.Handshake.Version (Version (..)) import Ouroboros.Network.Protocol.KeepAlive.Server (keepAliveServerPeer) --- import LeiosDemoOnlyTestFetch -import LeiosDemoOnlyTestNotify -import LeiosDemoTypes (LeiosPoint) +import LeiosDemoOnlyTestFetch +import LeiosDemoOnlyTestNotify +import qualified LeiosDemoLogic as LeiosLogic +import qualified LeiosDemoTypes as Leios immDBServer :: forall m blk addr. @@ -85,10 +87,11 @@ immDBServer :: -> ImmutableDB m blk -> NetworkMagic -> (SlotNo -> m DiffTime) - -> LeiosContext m + -> (ResourceRegistry m -> m (LeiosNotifyContext m)) + -> m (LeiosLogic.SomeLeiosFetchContext m) -> Versions NodeToNodeVersion NodeToNodeVersionData (OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode addr BL.ByteString m Void ()) -immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do +immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay mkLeiosNotifyContext mkLeiosFetchContext = do forAllVersions application where forAllVersions :: @@ -141,13 +144,11 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do leiosNotifyMiniProtocolNum (const Consensus.N2N.leiosNotifyProtocolLimits) leiosNotifyProt -{- , mkMiniProtocol Mux.StartOnDemand leiosFetchMiniProtocolNum (const Consensus.N2N.leiosFetchProtocolLimits) - undefined --} + leiosFetchProt ] where Consensus.N2N.Codecs { @@ -155,6 +156,7 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do , cChainSyncCodecSerialised , cBlockFetchCodecSerialised , cLeiosNotifyCodec + , cLeiosFetchCodec } = Consensus.N2N.defaultCodecs codecCfg blockVersion encAddr decAddr version @@ -178,13 +180,21 @@ immDBServer codecCfg encAddr decAddr immDB networkMagic getSlotDelay leios = do -- never reply, there is no timeout MiniProtocolCb $ \_ctx _channel -> forever $ threadDelay 10 leiosNotifyProt = - MiniProtocolCb $ \_ctx channel -> - runPeer nullTracer cLeiosNotifyCodec channel + MiniProtocolCb $ \_ctx channel -> id + $ withRegistry $ \reg -> id + $ mkLeiosNotifyContext reg >>= \leiosContext -> id + $ runPeer nullTracer cLeiosNotifyCodec channel $ leiosNotifyServerPeer - (MVar.takeMVar (leiosMailbox leios) <&> \case + (MVar.takeMVar (leiosMailbox leiosContext) <&> \case (p, Just sz) -> MsgLeiosBlockOffer p sz (p, Nothing) -> MsgLeiosBlockTxsOffer p ) + leiosFetchProt = + MiniProtocolCb $ \_ctx channel -> id + $ mkLeiosFetchContext >>= \(LeiosLogic.MkSomeLeiosFetchContext leiosContext) -> id + $ runPeer nullTracer cLeiosFetchCodec channel + $ leiosFetchServerPeer + $ pure (LeiosLogic.leiosFetchHandler leiosContext) mkMiniProtocol miniProtocolStart miniProtocolNum limits proto = MiniProtocol { miniProtocolNum @@ -298,6 +308,6 @@ data ImmDBServerException = ----- -data LeiosContext m = MkLeiosContext { - leiosMailbox :: MVar.MVar m (LeiosPoint, Maybe Word32) +data LeiosNotifyContext m = MkLeiosNotifyContext { + leiosMailbox :: !(MVar.MVar m (Leios.LeiosPoint, Maybe Word32)) } diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index aeefeba191..13f306d068 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -307,7 +307,7 @@ mkHandlers (atomically controlMessageSTM <&> \case Terminate -> Left () _ -> Right 300 {- TODO magic number -}) - (pure $ \case + (asTypeOf (pure $ const $ pure ()) $ pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 0c32041dff..be44e2b4c6 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -536,9 +536,9 @@ msgLeiosBlockTxsRequest db ebId bitmaps = do Just (64 * fromIntegral idx + i, (idx, bitmap') : k) txOffsets = unfoldr nextOffsetDESC (reverse bitmaps) -- fill in-memory table + withDieMsg $ DB.exec db (fromString sql_attach_memTxPoints) withDieMsg $ DB.exec db (fromString "BEGIN") do - withDieMsg $ DB.exec db (fromString sql_attach_memTxPoints) stmt <- withDieJust $ DB.prepare db (fromString sql_insert_memTxPoints) withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) forM_ txOffsets $ \txOffset -> do diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index c28c523c6e..78dc5ac5b1 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -319,6 +319,7 @@ library contra-tracer, deepseq, diff-containers >=1.2, + direct-sqlite, filelock, fingertree-rm >=1.0, fs-api ^>=0.3, diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index addae43472..c23e6504ed 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -1,18 +1,31 @@ {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module LeiosDemoLogic (module LeiosDemoLogic) where import Cardano.Slotting.Slot (SlotNo (..)) import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) import qualified Control.Concurrent.Class.MonadMVar as MVar +import Control.Monad (foldM, when) +import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits +import Data.Foldable (forM_) import Data.Functor ((<&>)) import qualified Data.IntMap as IntMap +import Data.List (unfoldr) import qualified Data.Map as Map -import Data.Word (Word64) -import LeiosDemoTypes (EbId (..), LeiosEbBodies, LeiosPoint (..)) +import Data.String (fromString) +import qualified Data.Vector as V +import qualified Data.Vector.Mutable as MV +import Data.Word (Word16, Word64) +import qualified Database.SQLite3.Direct as DB +import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosTx (..), TxHash (..)) import qualified LeiosDemoTypes as Leios +import qualified LeiosDemoOnlyTestFetch as LF + ebIdSlot :: EbId -> SlotNo ebIdSlot (MkEbId y) = SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) @@ -66,3 +79,201 @@ ebIdFromPointM mvar p = Just ebBodies' -> do -- TODO when to INSERT INTO ebPoints? pure (ebBodies', ebId) + +----- + +loadEbBodies :: Monad m => LeiosDb stmt m -> m LeiosEbBodies +loadEbBodies db = do + dbExec db (fromString "BEGIN") + stmt <- dbPrepare db (fromString sql_scan_ebId) + let loop !ps !qs = + dbStep db stmt >>= \case + DB.Done -> do + dbFinalize db stmt + pure (ps, qs) + DB.Row -> do + ebSlot <- fromIntegral <$> dbColumnInt64 db stmt 0 + ebHash <- MkEbHash <$> dbColumnBlob db stmt 1 + ebId <- fromIntegral <$> dbColumnInt64 db stmt 2 + loop + (IntMap.insertWith Map.union ebSlot (Map.singleton ebHash (MkEbId ebId)) ps) + (IntMap.insert ebId ebHash qs) + (ps, qs) <- loop IntMap.empty IntMap.empty + dbExec db (fromString "COMMIT") + pure Leios.emptyLeiosEbBodies { + Leios.ebPoints = ps + , + Leios.ebPointsInverse = qs + } + +sql_scan_ebId :: String +sql_scan_ebId = + "SELECT ebSlot, ebHashBytes, ebId\n\ + \FROM ebPoints\n\ + \ORDER BY ebId ASC\n\ + \" + +----- + +data SomeLeiosFetchContext m = + forall stmt. MkSomeLeiosFetchContext !(LeiosFetchContext stmt m) + +data LeiosFetchContext stmt m = MkLeiosFetchContext { + leiosDb :: !(LeiosDb stmt m) + , leiosEbBodies :: !LeiosEbBodies + , leiosEbBuffer :: !(MV.MVector (PrimState m) (TxHash, BytesSize)) + , leiosEbTxsBuffer :: !(MV.MVector (PrimState m) LeiosTx) + } + +leiosFetchHandler :: + PrimMonad m + => + LeiosFetchContext stmt m + -> + LF.LeiosFetchRequestHandler LeiosPoint LeiosEb LeiosTx m +leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case + LF.MsgLeiosBlockRequest p -> + LF.MsgLeiosBlock <$> msgLeiosBlockRequest leiosContext p + LF.MsgLeiosBlockTxsRequest p bitmaps -> + LF.MsgLeiosBlockTxs <$> msgLeiosBlockTxsRequest leiosContext p bitmaps + +msgLeiosBlockRequest :: PrimMonad m => LeiosFetchContext stmt m -> LeiosPoint -> m LeiosEb +msgLeiosBlockRequest leiosContext p = do + let MkLeiosFetchContext {leiosDb = db, leiosEbBodies, leiosEbBuffer = buf} = leiosContext + let ebId = fst $ ebIdFromPoint p leiosEbBodies + -- get the EB items + dbExec db (fromString "BEGIN") + stmt <- dbPrepare db (fromString sql_lookup_ebBodies) + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + let loop !i = + dbStep db stmt >>= \case + DB.Done -> do + dbFinalize db stmt + pure i + DB.Row -> do + txHashBytes <- dbColumnBlob db stmt 0 + txBytesSize <- fromIntegral <$> dbColumnInt64 db stmt 1 + MV.write buf i (MkTxHash txHashBytes, txBytesSize) + loop (i+1) + n <- loop 0 + dbExec db (fromString "COMMIT") + v <- V.freeze $ MV.slice 0 n buf + pure $ MkLeiosEb v + +sql_lookup_ebBodies :: String +sql_lookup_ebBodies = + "SELECT txHashBytes, txBytesSize FROM ebTxs\n\ + \WHERE ebId = ?\n\ + \ORDER BY txOffset ASC\n\ + \" + +msgLeiosBlockTxsRequest :: + PrimMonad m + => + LeiosFetchContext stmt m + -> + LeiosPoint + -> + [(Word16, Word64)] + -> + m (V.Vector LeiosTx) +msgLeiosBlockTxsRequest leiosContext p bitmaps = do + let MkLeiosFetchContext {leiosDb = db, leiosEbBodies, leiosEbTxsBuffer = buf} = leiosContext + let ebId = fst $ ebIdFromPoint p leiosEbBodies + do + let idxs = map fst bitmaps + let idxLimit = Leios.maxEbItems `div` 64 + when (any (== 0) $ map snd bitmaps) $ do + error "A bitmap is zero" + when (flip any idxs (> fromIntegral idxLimit)) $ do + error $ "An offset exceeds the theoretical limit " <> show idxLimit + when (not $ and $ zipWith (<) idxs (tail idxs)) $ do + error "Offsets not strictly ascending" + let nextOffset = \case + [] -> Nothing + (idx, bitmap) : k -> case popLeftmostOffset bitmap of + Nothing -> nextOffset k + Just (i, bitmap') -> + Just (64 * fromIntegral idx + i, (idx, bitmap') : k) + txOffsets = unfoldr nextOffset bitmaps + -- fill in-memory table + dbExec db (fromString sql_attach_memTxPoints) + dbExec db (fromString "BEGIN") + do + stmt <- dbPrepare db (fromString sql_insert_memTxPoints) + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + forM_ txOffsets $ \txOffset -> do + dbBindInt64 db stmt 2 (fromIntegral txOffset) + dbStep1 db stmt + dbReset db stmt + dbFinalize db stmt + -- get txBytess + stmt <- dbPrepare db (fromString sql_retrieve_from_ebTxs) + n <- (\f -> foldM f 0 txOffsets) $ \i txOffset -> do + dbStep db stmt >>= \case + DB.Done -> do + dbFinalize db stmt + pure i + DB.Row -> do + txOffset' <- dbColumnInt64 db stmt 0 + txBytes <- dbColumnBlob db stmt 1 + when (fromIntegral txOffset /= txOffset') $ do + error $ "Missing offset " ++ show (txOffset, txOffset') + MV.write buf i (MkLeiosTx txBytes) + pure $! (i + 1) + dbExec db (fromString "COMMIT") + dbExec db (fromString sql_detach_memTxPoints) + V.freeze $ MV.slice 0 n buf + +{- | For example +@ + print $ unfoldr popLeftmostOffset 0 + print $ unfoldr popLeftmostOffset 1 + print $ unfoldr popLeftmostOffset (2^(34 :: Int)) + print $ unfoldr popLeftmostOffset (2^(63 :: Int) + 2^(62 :: Int) + 8) + [] + [63] + [29] + [0,1,60] +@ +-} +popLeftmostOffset :: Word64 -> Maybe (Int, Word64) +{-# INLINE popLeftmostOffset #-} +popLeftmostOffset = \case + 0 -> Nothing + w -> let zs = Bits.countLeadingZeros w + in + Just (zs, Bits.clearBit w (63 - zs)) + +sql_attach_memTxPoints :: String +sql_attach_memTxPoints = + "ATTACH DATABASE ':memory:' AS mem;\n\ + \\n\ + \CREATE TABLE mem.txPoints (\n\ + \ ebId INTEGER NOT NULL\n\ + \ ,\n\ + \ txOffset INTEGER NOT NULL\n\ + \ ,\n\ + \ PRIMARY KEY (ebId ASC, txOffset ASC)\n\ + \ ) WITHOUT ROWID;\n\ + \" + +sql_detach_memTxPoints :: String +sql_detach_memTxPoints = + -- NB :memory: databases are discarded when detached + "DETACH DATABASE mem;\n\ + \" + +sql_insert_memTxPoints :: String +sql_insert_memTxPoints = + "INSERT INTO mem.txPoints (ebId, txOffset) VALUES (?, ?);\n\ + \" + +sql_retrieve_from_ebTxs :: String +sql_retrieve_from_ebTxs = + "SELECT x.txOffset, x.txBytes\n\ + \FROM ebTxs as x\n\ + \INNER JOIN mem.txPoints ON x.ebId = mem.txPoints.ebId AND x.txOffset = mem.txPoints.txOffset\n\ + \WHERE x.txBytes IS NOT NULL\n\ + \ORDER BY mem.txPoints.ebId ASC, mem.txPoints.txOffset ASC\n\ + \" diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 4e4a3d5e1f..c152d8f908 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -26,6 +26,7 @@ module LeiosDemoOnlyTestFetch , LeiosFetchClientPeer , LeiosFetchClientPeerPipelined , LeiosFetchServerPeer + , LeiosFetchRequestHandler (..) , leiosFetchClientPeer , leiosFetchClientPeerPipelined , leiosFetchServerPeer @@ -43,6 +44,7 @@ import Data.Kind (Type) import Data.Primitive.MutVar (MutVar) import qualified Data.Primitive.MutVar as Prim import Data.Singletons +import qualified Data.Vector as V import Data.Word (Word16, Word64) import qualified Network.Mux.Types as Mux import Network.TypedProtocol.Codec.CBOR @@ -117,7 +119,7 @@ instance Protocol (LeiosFetch point eb tx) where -> [(Word16, Word64)] -> Message (LeiosFetch point eb tx) StIdle (StBusy StBlockTxs) MsgLeiosBlockTxs - :: ![tx] + :: !(V.Vector tx) -> Message (LeiosFetch point eb tx) (StBusy StBlockTxs) StIdle -- MsgLeiosVotesRequest @@ -232,7 +234,8 @@ encodeLeiosFetch encodeP encodeEb encodeTx = encode MsgLeiosBlockTxs txs -> CBOR.encodeListLen 2 <> CBOR.encodeWord 3 - <> CBOR.encodeListLenIndef <> foldr (\tx r -> encodeTx tx <> r) CBOR.encodeBreak txs + <> CBOR.encodeListLen (fromIntegral $ V.length txs) + <> foldMap encodeTx txs -- MsgLeiosVotesRequest -- MsgLeiosVoteDelivery -- MsgLeiosBlockRangeRequest @@ -275,7 +278,12 @@ decodeLeiosFetch decodeP decodeEb decodeTx = decode bitmaps <- decodeBitmaps return $ SomeMessage $ MsgLeiosBlockTxsRequest p bitmaps (SingBlockTxs, 2, 3) -> do - txs <- CBOR.decodeListLenIndef *> CBOR.decodeSequenceLenIndef (flip (:)) [] reverse decodeTx + n <- CBOR.decodeListLen + -- TODO does V.generateM allocate exacly one buffer, via the hint? + -- + -- If not, we could do so manually by relying on the fact that + -- Decoder is ultimate in ST. + txs <- V.generateM n $ \_i -> decodeTx return $ SomeMessage $ MsgLeiosBlockTxs txs -- MsgLeiosVotesRequest -- MsgLeiosVoteDelivery @@ -360,11 +368,11 @@ decodeBitmaps = ----- -data SomeJob point eb tx m = +data SomeLeiosFetchJob point eb tx m = forall st'. StateTokenI (StBusy st') => - MkSomeJob + MkSomeLeiosFetchJob (Message (LeiosFetch point eb tx) StIdle (StBusy st')) (m (Message (LeiosFetch point eb tx) (StBusy st') StIdle -> m ())) @@ -375,7 +383,7 @@ leiosFetchClientPeer :: forall m point eb tx a. Monad m => - m (Either a (SomeJob point eb tx m)) + m (Either a (SomeLeiosFetchJob point eb tx m)) -> Peer (LeiosFetch point eb tx) AsClient NonPipelined StIdle m a leiosFetchClientPeer checkDone = @@ -386,7 +394,7 @@ leiosFetchClientPeer checkDone = Left x -> Yield ReflClientAgency MsgDone $ Done ReflNobodyAgency x - Right (MkSomeJob req k) -> case req of + Right (MkSomeLeiosFetchJob req k) -> case req of MsgLeiosBlockRequest{} -> do Yield ReflClientAgency req $ Await ReflServerAgency $ \rsp -> case rsp of @@ -403,7 +411,7 @@ leiosFetchClientPeer checkDone = type LeiosFetchServerPeer point eb tx m a = Peer (LeiosFetch point eb tx) AsServer NonPipelined StIdle m () -newtype RequestHandler point eb tx m = MkRequestHandler ( +newtype LeiosFetchRequestHandler point eb tx m = MkLeiosFetchRequestHandler ( forall st'. Message (LeiosFetch point eb tx) StIdle (StBusy st') -> @@ -414,7 +422,7 @@ leiosFetchServerPeer :: forall m point eb tx. Monad m => - m (RequestHandler point eb tx m) + m (LeiosFetchRequestHandler point eb tx m) -> Peer (LeiosFetch point eb tx) AsServer NonPipelined StIdle m () leiosFetchServerPeer handler = @@ -424,13 +432,13 @@ leiosFetchServerPeer handler = go = Await ReflClientAgency $ \req -> case req of MsgDone -> Done ReflNobodyAgency () MsgLeiosBlockRequest{} -> Effect $ do - MkRequestHandler f <- handler + MkLeiosFetchRequestHandler f <- handler rsp <- f req pure $ Yield ReflServerAgency rsp $ go MsgLeiosBlockTxsRequest{} -> Effect $ do - MkRequestHandler f <- handler + MkLeiosFetchRequestHandler f <- handler rsp <- f req pure $ Yield ReflServerAgency rsp @@ -453,7 +461,7 @@ leiosFetchClientPeerPipelined :: forall m point eb tx a. PrimMonad m => - m (Either (m (Either a (SomeJob point eb tx m))) (Either a (SomeJob point eb tx m))) + m (Either (m (Either a (SomeLeiosFetchJob point eb tx m))) (Either a (SomeLeiosFetchJob point eb tx m))) -- ^ either the return value or the next job, or a blocking request for those two -> PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a @@ -476,7 +484,7 @@ leiosFetchClientPeerPipelined tryNext = (\MkC -> go1 stop m) Right x -> pure $ go2 stop n x - go2 :: MutVar (PrimState m) WhetherDraining -> Nat n -> Either a (SomeJob point eb tx m) -> X point eb tx m a n + go2 :: MutVar (PrimState m) WhetherDraining -> Nat n -> Either a (SomeLeiosFetchJob point eb tx m) -> X point eb tx m a n go2 stop !n = \case Left x -> Effect $ do Prim.writeMutVar stop AlreadyDraining @@ -489,8 +497,8 @@ leiosFetchClientPeerPipelined tryNext = (Just $ send stop n job) (\MkC -> go1 stop m) - send :: MutVar (PrimState m) WhetherDraining -> Nat n -> SomeJob point eb tx m -> X point eb tx m a n - send stop !n (MkSomeJob req k) = + send :: MutVar (PrimState m) WhetherDraining -> Nat n -> SomeLeiosFetchJob point eb tx m -> X point eb tx m a n + send stop !n (MkSomeLeiosFetchJob req k) = YieldPipelined ReflClientAgency req diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 29033e7c09..ec6a8ef6c5 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE LambdaCase #-} + module LeiosDemoTypes (module LeiosDemoTypes) where import Cardano.Binary (enforceSize) @@ -10,6 +12,7 @@ import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) import Control.Concurrent.Class.MonadSTM (TVar) import Data.ByteString (ByteString) +import Data.Int (Int64) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.Map (Map) @@ -20,13 +23,18 @@ import qualified Data.Set as Set import Data.String (fromString) import qualified Data.Vector as V import Data.Word (Word16, Word32, Word64) +import qualified Database.SQLite3.Direct as DB import Ouroboros.Consensus.Util (ShowProxy (..)) +import System.Exit (die) type BytesSize = Word32 newtype EbId = MkEbId Int deriving (Eq, Ord) +fromIntegralEbId :: Integral a => EbId -> a +fromIntegralEbId (MkEbId x) = fromIntegral x + newtype PeerId a = MkPeerId a deriving (Eq, Ord) @@ -206,3 +214,95 @@ decodeLeiosEb = do -- ultimate in ST. fmap MkLeiosEb $ V.generateM n $ \_i -> do (,) <$> (fmap MkTxHash CBOR.decodeBytes) <*> CBOR.decodeWord32 + +----- + +maxMsgLeiosBlockBytesSize :: BytesSize +maxMsgLeiosBlockBytesSize = 500 * 10^(3 :: Int) -- from CIP-0164's recommendations + +minEbItemBytesSize :: BytesSize +minEbItemBytesSize = (32 - hashOverhead) + minSizeOverhead + where + hashOverhead = 1 + 1 -- bytestring major byte + a length = 32 + minSizeOverhead = 1 + 1 -- int major byte + a value at low as 55 + +maxEbItems :: Int +maxEbItems = + fromIntegral + $ (maxMsgLeiosBlockBytesSize - msgOverhead - sequenceOverhead) + `div` + minEbItemBytesSize + where + msgOverhead = 1 + 1 -- short list len + small word + sequenceOverhead = 1 + 2 -- sequence major byte + a length > 255 + +----- + +data LeiosDb stmt m = MkLeiosDb { + dbBindBlob :: !(stmt -> DB.ParamIndex -> ByteString -> m ()) + , + dbBindInt64 :: !(stmt -> DB.ParamIndex -> Int64 -> m ()) + , + dbColumnBlob :: !(stmt -> DB.ColumnIndex -> m ByteString) + , + dbColumnInt64 :: !(stmt -> DB.ColumnIndex -> m Int64) + , + dbExec :: !(DB.Utf8 -> m ()) + , + dbFinalize :: !(stmt -> m ()) + , + dbPrepare :: !(DB.Utf8 -> m stmt) + , + dbReset :: !(stmt -> m ()) + , + dbStep :: !(stmt -> m DB.StepResult) + , + dbStep1 :: !(stmt -> m ()) + } + +leiosDbFromSqliteDirect :: DB.Database -> LeiosDb DB.Statement IO +leiosDbFromSqliteDirect db = MkLeiosDb { + dbBindBlob = \stmt p v -> withDie $ DB.bindBlob stmt p v + , + dbBindInt64 = \stmt p v -> withDie $ DB.bindInt64 stmt p v + , + dbColumnBlob = \stmt c -> DB.columnBlob stmt c + , + dbColumnInt64 = \stmt c -> DB.columnInt64 stmt c + , + dbExec = \q -> withDieMsg $ DB.exec db q + , + dbFinalize = \stmt -> withDie $ DB.finalize stmt + , + dbPrepare = \q -> withDieJust $ DB.prepare db q + , + dbReset = \stmt -> withDie $ DB.reset stmt + , + dbStep = \stmt -> withDie $ DB.stepNoCB stmt + , + dbStep1 = \stmt -> withDieDone $ DB.stepNoCB stmt + } + +withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a +withDiePoly f io = + io >>= \case + Left e -> die $ show $ f e + Right x -> pure x + +withDieMsg :: IO (Either (DB.Error, DB.Utf8) a) -> IO a +withDieMsg = withDiePoly snd + +withDie :: IO (Either DB.Error a) -> IO a +withDie = withDiePoly id + +withDieJust :: IO (Either DB.Error (Maybe a)) -> IO a +withDieJust io = + withDie io >>= \case + Nothing -> die "impossible!" + Just x -> pure x + +withDieDone :: IO (Either DB.Error DB.StepResult) -> IO () +withDieDone io = + withDie io >>= \case + DB.Row -> die "impossible!" + DB.Done -> pure () diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index a7b4e4c0e4..f2993bb8f6 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -33,6 +33,11 @@ if [[ -z "${LEIOS_SCHEDULE}" ]]; then exit 1 fi +if [[ -z "${LEIOS_DB}" ]]; then + echo "Error: \${LEIOS_DB} must be the path to an exist Leios database." >&2 + exit 1 +fi + if [[ -z "${REF_SLOT}" ]] || [[ ! "$REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$REF_SLOT" -lt 0 ]]; then echo "Error: \${REF_SLOT} must be a non-negative integer, a slot number" >&2 exit 1 @@ -166,6 +171,7 @@ IMMDB_CMD_CORE="${IMMDB_SERVER} \ --initial-slot $REF_SLOT \ --initial-time $ONSET_OF_REF_SLOT --leios-schedule $LEIOS_SCHEDULE + --leios-db $LEIOS_DB --port ${PORT1}" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" From f9dc066c2dc179d4f28f3d1b757d1bb2bddb6b75 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 10:49:42 -0700 Subject: [PATCH 086/119] leiosdemo202510: fixup LeiosNotify client --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 11 ++++++++--- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 11 +++++++++++ 2 files changed, 19 insertions(+), 3 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 13f306d068..75000c3e41 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -307,7 +307,7 @@ mkHandlers (atomically controlMessageSTM <&> \case Terminate -> Left () _ -> Right 300 {- TODO magic number -}) - (asTypeOf (pure $ const $ pure ()) $ pure $ \case + (pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do @@ -323,7 +323,7 @@ mkHandlers peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars case Map.lookup (Leios.MkPeerId peer) peersVars of - Nothing -> error "TODO" + Nothing -> error "impossible!" Just x -> pure x MVar.modifyMVar_ (Leios.offerings peerVars) $ \(offers1, offers2) -> do let !offers1' = Set.insert ebId offers1 @@ -334,7 +334,7 @@ mkHandlers peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars case Map.lookup (Leios.MkPeerId peer) peersVars of - Nothing -> error "TODO" + Nothing -> error "impossible!" Just x -> pure x MVar.modifyMVar_ (Leios.offerings peerVars) $ \(offers1, offers2) -> do let !offers2' = Set.insert ebId offers2 @@ -959,6 +959,11 @@ mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucke eicConnectionId = them, eicControlMessage = controlMessageSTM } channel = do + let NodeKernel { getLeiosPeersVars } = kernel + MVar.modifyMVar_ getLeiosPeersVars $ \leiosPeersVars -> do + x <- Leios.newLeiosPeerVars + let !leiosPeersVars' = Map.insert (Leios.MkPeerId them) x leiosPeersVars + pure leiosPeersVars' labelThisThread "LeiosNotifyClient" ((), trailing) <- runPipelinedPeerWithLimits (TraceLabelPeer them `contramap` tLeiosNotifyTracer) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index ec6a8ef6c5..bb4eddcf33 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -1,4 +1,5 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module LeiosDemoTypes (module LeiosDemoTypes) where @@ -10,7 +11,9 @@ import Codec.CBOR.Encoding (Encoding) import qualified Codec.CBOR.Encoding as CBOR import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) +import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Concurrent.Class.MonadSTM (TVar) +import qualified Control.Concurrent.Class.MonadSTM as STM import Data.ByteString (ByteString) import Data.Int (Int64) import Data.IntMap (IntMap) @@ -18,6 +21,7 @@ import qualified Data.IntMap as IntMap import Data.Map (Map) import qualified Data.Map as Map import Data.Sequence (Seq) +import qualified Data.Sequence as Seq import Data.Set (Set) import qualified Data.Set as Set import Data.String (fromString) @@ -25,6 +29,7 @@ import qualified Data.Vector as V import Data.Word (Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB import Ouroboros.Consensus.Util (ShowProxy (..)) +import Ouroboros.Consensus.Util.IOLike (IOLike) import System.Exit (die) type BytesSize = Word32 @@ -115,6 +120,12 @@ data LeiosPeerVars m = MkLeiosPeerVars { requestsToSend :: !(TVar m (Seq LeiosFetchRequest)) } +newLeiosPeerVars :: IOLike m => m (LeiosPeerVars m) +newLeiosPeerVars = do + offerings <- MVar.newMVar (Set.empty, Set.empty) + requestsToSend <- STM.newTVarIO Seq.empty + pure MkLeiosPeerVars {offerings, requestsToSend} + data LeiosEbBodies = MkLeiosEbBodies { acquiredEbBodies :: !(Set EbId) , From 6a25c0bc0bf50176de9d475b0c763796a2079919 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 11:18:37 -0700 Subject: [PATCH 087/119] leiosdemo202510: add LeiosFetch server to node --- .../ouroboros-consensus-cardano.cabal | 1 - .../Cardano/Tools/ImmDBServer/Diffusion.hs | 9 +++-- .../Ouroboros/Consensus/Network/NodeToNode.hs | 16 ++++++--- .../Ouroboros/Consensus/Node.hs | 8 +++++ .../Ouroboros/Consensus/NodeKernel.hs | 6 ++++ .../src/ouroboros-consensus/LeiosDemoLogic.hs | 35 +++++++++++++++---- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 3 ++ 7 files changed, 60 insertions(+), 18 deletions(-) diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index b60e2b13e7..7e2fb3e230 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -592,7 +592,6 @@ library unstable-cardano-tools text-builder >=1, transformers, transformers-except, - vector, executable db-analyser import: common-lib diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index 2e45a8e009..ae39d30017 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -21,7 +21,6 @@ import qualified Data.Map.Strict as Map import Data.String (fromString) import qualified Data.Text as T import qualified Data.Text.Encoding as T -import qualified Data.Vector.Mutable as MV import Data.Void (Void) import Data.Word (Word32, Word64) import qualified Database.SQLite3.Direct as DB @@ -115,8 +114,6 @@ run immDBDir sockAddr cfg getSlotDelay leiosDbFile leiosSchedule = withRegistry pure leiosNotifyContext let mkLeiosFetchContext = do -- each LeiosFetch server calls this when it initializes - leiosEbBuffer <- MV.new Leios.maxEbItems - leiosEbTxsBuffer <- MV.new Leios.maxEbItems Dir.doesFileExist leiosDbFile >>= \case False -> die $ "The Leios database must already exist: " <> show leiosDbFile True -> pure () @@ -124,8 +121,10 @@ run immDBDir sockAddr cfg getSlotDelay leiosDbFile leiosSchedule = withRegistry Left (_err, utf8) -> die $ show utf8 Right x -> pure $ Leios.leiosDbFromSqliteDirect x leiosEbBodies <- LeiosLogic.loadEbBodies leiosDb - let leiosFetchContext = LeiosLogic.MkLeiosFetchContext { LeiosLogic.leiosDb, LeiosLogic.leiosEbBodies, LeiosLogic.leiosEbBuffer, LeiosLogic.leiosEbTxsBuffer } - pure $ LeiosLogic.MkSomeLeiosFetchContext leiosFetchContext + fmap LeiosLogic.MkSomeLeiosFetchContext + $ LeiosLogic.newLeiosFetchContext + leiosDb + (pure leiosEbBodies) ImmutableDB.withDB (ImmutableDB.openDB (immDBArgs registry) runWithTempRegistry) \immDB -> serve sockAddr $ MP.immDBServer diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 75000c3e41..c37e25f4bd 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -62,6 +62,7 @@ import Data.Map.Strict (Map) import Data.Void (Void) import qualified Network.Mux as Mux import Network.TypedProtocol.Codec +import Network.TypedProtocol.Peer (Peer (Effect)) import Ouroboros.Consensus.Block import Ouroboros.Consensus.Config (DiffusionPipeliningSupport (..)) import Ouroboros.Consensus.HeaderValidation (HeaderWithTime) @@ -349,14 +350,19 @@ mkHandlers (pure $ Left $ atomically $ controlMessageSTM >>= \case Terminate -> pure $ Left () _ -> retry - ) -- TODO - , hLeiosFetchServer = \_version _peer -> - leiosFetchServerPeer - (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO + ) + , hLeiosFetchServer = \_version _peer -> Effect $ do + Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection + leiosFetchContext <- + Leios.newLeiosFetchContext + db + (MVar.readMVar getLeiosEbBodies) + pure $ leiosFetchServerPeer + (pure $ Leios.leiosFetchHandler leiosFetchContext) } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel - NodeKernel {getLeiosPeersVars, getLeiosEbBodies, getLeiosReady} = nodeKernel + NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosReady} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs index 01f527fe2b..e52521fcba 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs @@ -162,6 +162,8 @@ import System.FS.API.Types (MountPoint (..)) import System.FS.IO (ioHasFS) import System.Random (StdGen, newStdGen, randomIO, split) +import LeiosDemoTypes (SomeLeiosDb) + {------------------------------------------------------------------------------- The arguments to the Consensus Layer node functionality -------------------------------------------------------------------------------} @@ -225,6 +227,8 @@ data RunNodeArgs m addrNTN addrNTC blk p2p = RunNodeArgs { , rnGetUseBootstrapPeers :: STM m UseBootstrapPeers , rnGenesisConfig :: GenesisConfig + + , rnNewLeiosDbConnection :: m (SomeLeiosDb m) } @@ -587,6 +591,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} = llrnPublicPeerSelectionStateVar genesisArgs DiffusionPipeliningOn + rnNewLeiosDbConnection nodeKernel <- initNodeKernel nodeKernelArgs rnNodeKernelHook registry nodeKernel @@ -841,6 +846,7 @@ mkNodeKernelArgs :: -> StrictSTM.StrictTVar m (PublicPeerSelectionState addrNTN) -> GenesisNodeKernelArgs m blk -> DiffusionPipeliningSupport + -> m (SomeLeiosDb m) -> m (NodeKernelArgs m addrNTN (ConnectionId addrNTC) blk) mkNodeKernelArgs registry @@ -860,6 +866,7 @@ mkNodeKernelArgs publicPeerSelectionStateVar genesisArgs getDiffusionPipeliningSupport + nkaGetLeiosNewDbConnection = do let (kaRng, psRng) = split rng return NodeKernelArgs @@ -887,6 +894,7 @@ mkNodeKernelArgs , publicPeerSelectionStateVar , genesisArgs , getDiffusionPipeliningSupport + , nkaGetLeiosNewDbConnection } -- | We allow the user running the node to customise the 'NodeKernelArgs' diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index e52a8abcd9..a57479c9cb 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -194,6 +194,7 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- noticeably awkward fit for this logic. -- See 'LeiosPeerVars' for the write patterns + , getLeiosNewDbConnection :: m (SomeLeiosDb m) , getLeiosPeersVars :: MVar m (Map (PeerId (ConnectionId addrNTN)) (LeiosPeerVars m)) -- written to by the LeiosNotify&LeiosFetch clients (TODO and by -- eviction) @@ -236,6 +237,8 @@ data NodeKernelArgs m addrNTN addrNTC blk = NodeKernelArgs { :: StrictSTM.StrictTVar m (PublicPeerSelectionState addrNTN) , genesisArgs :: GenesisNodeKernelArgs m blk , getDiffusionPipeliningSupport :: DiffusionPipeliningSupport + + , nkaGetLeiosNewDbConnection :: m (SomeLeiosDb m) } initNodeKernel :: @@ -258,6 +261,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , publicPeerSelectionStateVar , genesisArgs , getDiffusionPipeliningSupport + , nkaGetLeiosNewDbConnection } = do -- using a lazy 'TVar', 'BlockForging' does not have a 'NoThunks' instance. blockForgingVar :: LazySTM.TMVar m [BlockForging m blk] <- LazySTM.newTMVarIO [] @@ -362,6 +366,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers fetchClientRegistry blockFetchConfiguration + let getLeiosNewDbConnection = nkaGetLeiosNewDbConnection getLeiosPeersVars <- MVar.newMVar Map.empty getLeiosEbBodies <- MVar.newMVar emptyLeiosEbBodies getLeiosOutstanding <- MVar.newMVar emptyLeiosOutstanding @@ -385,6 +390,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getDiffusionPipeliningSupport , getBlockchainTime = btime + , getLeiosNewDbConnection , getLeiosPeersVars , getLeiosEbBodies , getLeiosOutstanding diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index c23e6504ed..98772f88d2 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -21,11 +21,10 @@ import qualified Data.Vector as V import qualified Data.Vector.Mutable as MV import Data.Word (Word16, Word64) import qualified Database.SQLite3.Direct as DB +import qualified LeiosDemoOnlyTestFetch as LF import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosTx (..), TxHash (..)) import qualified LeiosDemoTypes as Leios -import qualified LeiosDemoOnlyTestFetch as LF - ebIdSlot :: EbId -> SlotNo ebIdSlot (MkEbId y) = SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) @@ -120,11 +119,27 @@ data SomeLeiosFetchContext m = data LeiosFetchContext stmt m = MkLeiosFetchContext { leiosDb :: !(LeiosDb stmt m) - , leiosEbBodies :: !LeiosEbBodies , leiosEbBuffer :: !(MV.MVector (PrimState m) (TxHash, BytesSize)) , leiosEbTxsBuffer :: !(MV.MVector (PrimState m) LeiosTx) + , readLeiosEbBodies :: !(m LeiosEbBodies) } +newLeiosFetchContext :: + PrimMonad m + => + LeiosDb stmt m + -> + m LeiosEbBodies + -> + m (LeiosFetchContext stmt m) +newLeiosFetchContext leiosDb readLeiosEbBodies = do + -- each LeiosFetch server calls this when it initializes + leiosEbBuffer <- MV.new Leios.maxEbItems + leiosEbTxsBuffer <- MV.new Leios.maxEbItems + pure MkLeiosFetchContext { leiosDb, leiosEbBuffer, leiosEbTxsBuffer, readLeiosEbBodies} + +----- + leiosFetchHandler :: PrimMonad m => @@ -139,8 +154,11 @@ leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case msgLeiosBlockRequest :: PrimMonad m => LeiosFetchContext stmt m -> LeiosPoint -> m LeiosEb msgLeiosBlockRequest leiosContext p = do - let MkLeiosFetchContext {leiosDb = db, leiosEbBodies, leiosEbBuffer = buf} = leiosContext - let ebId = fst $ ebIdFromPoint p leiosEbBodies + let MkLeiosFetchContext {leiosDb = db, leiosEbBuffer = buf, readLeiosEbBodies} = leiosContext + (ebId, mbLeiosEbBodies') <- readLeiosEbBodies <&> ebIdFromPoint p + case mbLeiosEbBodies' of + Nothing -> pure () + Just _ -> error "Unrecognized Leios point" -- get the EB items dbExec db (fromString "BEGIN") stmt <- dbPrepare db (fromString sql_lookup_ebBodies) @@ -178,8 +196,11 @@ msgLeiosBlockTxsRequest :: -> m (V.Vector LeiosTx) msgLeiosBlockTxsRequest leiosContext p bitmaps = do - let MkLeiosFetchContext {leiosDb = db, leiosEbBodies, leiosEbTxsBuffer = buf} = leiosContext - let ebId = fst $ ebIdFromPoint p leiosEbBodies + let MkLeiosFetchContext {leiosDb = db, leiosEbTxsBuffer = buf, readLeiosEbBodies} = leiosContext + (ebId, mbLeiosEbBodies') <- readLeiosEbBodies <&> ebIdFromPoint p + case mbLeiosEbBodies' of + Nothing -> pure () + Just _ -> error "Unrecognized Leios point" do let idxs = map fst bitmaps let idxLimit = Leios.maxEbItems `div` 64 diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index bb4eddcf33..0c16d672d5 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} @@ -249,6 +250,8 @@ maxEbItems = ----- +data SomeLeiosDb m = forall stmt. MkSomeLeiosDb (LeiosDb stmt m) + data LeiosDb stmt m = MkLeiosDb { dbBindBlob :: !(stmt -> DB.ParamIndex -> ByteString -> m ()) , From 43b6bb80637ba7d1e4072d81bccd42b8f6aa8f65 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 11:38:27 -0700 Subject: [PATCH 088/119] leiosdemo202510: more direct LeiosNotify server --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 14 +++++++------- .../ouroboros-consensus/LeiosDemoOnlyTestFetch.hs | 10 ++++++++-- .../ouroboros-consensus/LeiosDemoOnlyTestNotify.hs | 10 ++++++++-- 3 files changed, 23 insertions(+), 11 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index c37e25f4bd..3a806dc67b 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -303,8 +303,12 @@ mkHandlers , hKeepAliveServer = \_version _peer -> keepAliveServer , hPeerSharingClient = \_version controlMessageSTM _peer -> peerSharingClient controlMessageSTM , hPeerSharingServer = \_version _peer -> peerSharingServer getPeerSharingAPI - , hLeiosNotifyClient = \_version controlMessageSTM peer -> - leiosNotifyClientPeerPipelined + , hLeiosNotifyClient = \_version controlMessageSTM peer -> toLeiosNotifyClientPeerPipelined $ Effect $ do + MVar.modifyMVar_ getLeiosPeersVars $ \leiosPeersVars -> do + x <- Leios.newLeiosPeerVars + let !leiosPeersVars' = Map.insert (Leios.MkPeerId peer) x leiosPeersVars + pure leiosPeersVars' + pure $ leiosNotifyClientPeerPipelined (atomically controlMessageSTM <&> \case Terminate -> Left () _ -> Right 300 {- TODO magic number -}) @@ -346,6 +350,7 @@ mkHandlers leiosNotifyServerPeer (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO , hLeiosFetchClient = \_version controlMessageSTM _peer -> + , hLeiosFetchClient = \_version controlMessageSTM _peer -> toLeiosFetchClientPeerPipelined $ leiosFetchClientPeerPipelined (pure $ Left $ atomically $ controlMessageSTM >>= \case Terminate -> pure $ Left () @@ -965,11 +970,6 @@ mkApps kernel Tracers {..} mkCodecs ByteLimits {..} genChainSyncTimeout lopBucke eicConnectionId = them, eicControlMessage = controlMessageSTM } channel = do - let NodeKernel { getLeiosPeersVars } = kernel - MVar.modifyMVar_ getLeiosPeersVars $ \leiosPeersVars -> do - x <- Leios.newLeiosPeerVars - let !leiosPeersVars' = Map.insert (Leios.MkPeerId them) x leiosPeersVars - pure leiosPeersVars' labelThisThread "LeiosNotifyClient" ((), trailing) <- runPipelinedPeerWithLimits (TraceLabelPeer them `contramap` tLeiosNotifyTracer) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index c152d8f908..2de0496310 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -30,6 +30,7 @@ module LeiosDemoOnlyTestFetch , leiosFetchClientPeer , leiosFetchClientPeerPipelined , leiosFetchServerPeer + , toLeiosFetchClientPeerPipelined ) where import qualified Codec.CBOR.Decoding as CBOR @@ -453,6 +454,11 @@ type X point eb tx m a n = type LeiosFetchClientPeerPipelined point eb tx m a = PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a +toLeiosFetchClientPeerPipelined :: + Peer (LeiosFetch point eb tx) AsClient (Pipelined Z C) StIdle m a + -> LeiosFetchClientPeerPipelined point eb tx m a +toLeiosFetchClientPeerPipelined = PeerPipelined + data C = MkC data WhetherDraining = AlreadyDraining | NotYetDraining @@ -464,9 +470,9 @@ leiosFetchClientPeerPipelined :: m (Either (m (Either a (SomeLeiosFetchJob point eb tx m))) (Either a (SomeLeiosFetchJob point eb tx m))) -- ^ either the return value or the next job, or a blocking request for those two -> - PeerPipelined (LeiosFetch point eb tx) AsClient StIdle m a + Peer (LeiosFetch point eb tx) AsClient (Pipelined Z C) StIdle m a leiosFetchClientPeerPipelined tryNext = - PeerPipelined $ Effect $ do + Effect $ do stop <- Prim.newMutVar NotYetDraining pure $ go1 stop Zero where diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs index 8d42ebd244..99e4b812ee 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestNotify.hs @@ -29,6 +29,7 @@ module LeiosDemoOnlyTestNotify , leiosNotifyClientPeer , leiosNotifyClientPeerPipelined , leiosNotifyServerPeer + , toLeiosNotifyClientPeerPipelined ) where import qualified Codec.CBOR.Decoding as CBOR @@ -365,6 +366,11 @@ type X point announcement m a n = type LeiosNotifyClientPeerPipelined point announcement m a = PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a +toLeiosNotifyClientPeerPipelined :: + Peer (LeiosNotify point announcement) AsClient (Pipelined Z C) StIdle m a + -> LeiosNotifyClientPeerPipelined point announcement m a +toLeiosNotifyClientPeerPipelined = PeerPipelined + data C = MkC data WhetherDraining = AlreadyDraining | NotYetDraining @@ -378,9 +384,9 @@ leiosNotifyClientPeerPipelined :: -> m (Message (LeiosNotify point announcement) StBusy StIdle -> m ()) -> - PeerPipelined (LeiosNotify point announcement) AsClient StIdle m a + Peer (LeiosNotify point announcement) AsClient (Pipelined Z C) StIdle m a leiosNotifyClientPeerPipelined checkDone k0 = - PeerPipelined $ Effect $ do + Effect $ do stop <- Prim.newMutVar NotYetDraining pure $ go stop Zero where From 9c5584f8eeb7316e061df250ce1dacc5c80c12ff Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 12:40:18 -0700 Subject: [PATCH 089/119] leiosdemo202510: add fetch decision logic to node --- .../Ouroboros/Consensus/NodeKernel.hs | 32 ++- ouroboros-consensus/app/leiosdemo202510.hs | 12 +- ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../src/ouroboros-consensus/LeiosDemoLogic.hs | 272 +++++++++++++++++- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 91 ++++-- 5 files changed, 370 insertions(+), 38 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index a57479c9cb..dfcf220ded 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -132,7 +132,9 @@ import qualified Control.Concurrent.Class.MonadMVar as MVar import Data.Map (Map) import qualified Data.Map as Map -import LeiosDemoTypes +import LeiosDemoTypes (LeiosEbBodies, LeiosOutstanding, LeiosPeerVars, SomeLeiosDb) +import qualified LeiosDemoTypes as Leios +import qualified LeiosDemoLogic as Leios {------------------------------------------------------------------------------- Relay node @@ -195,15 +197,13 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- See 'LeiosPeerVars' for the write patterns , getLeiosNewDbConnection :: m (SomeLeiosDb m) - , getLeiosPeersVars :: MVar m (Map (PeerId (ConnectionId addrNTN)) (LeiosPeerVars m)) + , getLeiosPeersVars :: MVar m (Map (Leios.PeerId (ConnectionId addrNTN)) (LeiosPeerVars m)) -- written to by the LeiosNotify&LeiosFetch clients (TODO and by -- eviction) , getLeiosEbBodies :: MVar m LeiosEbBodies - -- written to by the fetch logic and by the LeiosNotify&LeiosFetch + -- written to by the fetch logic, by the LeiosNotify&LeiosFetch, and by LeiosCopier -- clients (TODO and by eviction) , getLeiosOutstanding :: MVar m (LeiosOutstanding (ConnectionId addrNTN)) - -- written to by the fetch logic and by the LeiosCopier - , getLeiosToCopy :: MVar m LeiosToCopy -- | Leios fetch logic 'MVar.takeMVar's before it runs -- -- LeiosNotify clients, LeiosFetch clients, and the LeiosCopier @@ -368,11 +368,26 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers let getLeiosNewDbConnection = nkaGetLeiosNewDbConnection getLeiosPeersVars <- MVar.newMVar Map.empty - getLeiosEbBodies <- MVar.newMVar emptyLeiosEbBodies - getLeiosOutstanding <- MVar.newMVar emptyLeiosOutstanding - getLeiosToCopy <- MVar.newMVar emptyLeiosToCopy + getLeiosEbBodies <- MVar.newMVar Leios.emptyLeiosEbBodies + getLeiosOutstanding <- MVar.newMVar Leios.emptyLeiosOutstanding getLeiosReady <- MVar.newEmptyMVar + void $ forkLinkedThread registry "NodeKernel.leiosFetchLogic" $ forever $ do + () <- MVar.takeMVar getLeiosReady + leiosPeersVars <- MVar.readMVar getLeiosPeersVars + offerings <- mapM (MVar.readMVar . Leios.offerings) leiosPeersVars + ebBodies <- MVar.readMVar getLeiosEbBodies + newDecisions <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do + pure $ Leios.leiosFetchLogicIteration + Leios.demoLeiosFetchStaticEnv + (ebBodies, offerings) + outstanding + let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions + (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> + atomically $ do + StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) + threadDelay (0.050 :: DiffTime) -- TODO magic number + return NodeKernel { getChainDB = chainDB , getMempool = mempool @@ -394,7 +409,6 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getLeiosPeersVars , getLeiosEbBodies , getLeiosOutstanding - , getLeiosToCopy , getLeiosReady } where diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index be44e2b4c6..5de8e99f4e 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -1118,7 +1118,7 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv { cachedTxs :: Map TxHash BytesSize , -- | All missing txs in the context of EBs worth retrieving the closure for - ebBodies :: Map EbId (IntMap (TxHash, BytesSize)) + missingEbTxs :: Map EbId (IntMap (TxHash, BytesSize)) , -- | @slot -> hash -> EbId@ -- @@ -1158,9 +1158,9 @@ data LeiosFetchDynamicEnv = MkLeiosFetchDynamicEnv { -- | Txs listed in received EBs but never themselves received missingTxBodies :: Set TxHash , - -- | Reverse index of 'ebBodies' + -- | Reverse index of 'missingEbTxs' -- - -- INVARIANT: @let (ebId, txOffset) = txOffsetss Map.! h in h = fst ((ebBodies IntMap.! ebId) IntMap.! txOffset)@ + -- INVARIANT: @let (ebId, txOffset) = txOffsetss Map.! h in h = fst ((missingEbTxs IntMap.! ebId) IntMap.! txOffset)@ txOffsetss :: Map TxHash (Map EbId Int) } @@ -1222,7 +1222,7 @@ loadLeiosFetchDynEnvHelper full db = do pure MkLeiosFetchDynamicEnv { cachedTxs = cached , - ebBodies = bodies + missingEbTxs = bodies , ebPoints = ps , @@ -1278,7 +1278,7 @@ leiosFetchLogicIteration env dynEnv = go1 acc emptyLeiosFetchDecisions $ expand $ Map.toDescList - $ Map.map Left (missingEbBodies acc) `Map.union` Map.map Right (ebBodies dynEnv) + $ Map.map Left (missingEbBodies acc) `Map.union` Map.map Right (missingEbTxs dynEnv) where expand = \case [] -> [] @@ -1382,7 +1382,7 @@ leiosFetchLogicIteration env dynEnv = -- there's a peer who offered it and we haven't already requested it from them = let txBytesSize = case Map.lookupMax txOffsets' of Nothing -> error "impossible!" - Just (ebId, txOffset) -> case Map.lookup ebId (ebBodies dynEnv) of + Just (ebId, txOffset) -> case Map.lookup ebId (missingEbTxs dynEnv) of Nothing -> error "impossible!" Just v -> snd $ v IntMap.! txOffset accNew' = diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 78dc5ac5b1..397b367bca 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -320,6 +320,7 @@ library deepseq, diff-containers >=1.2, direct-sqlite, + dlist, filelock, fingertree-rm >=1.0, fs-api ^>=0.3, diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 98772f88d2..b032a31d67 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -2,6 +2,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE ScopedTypeVariables #-} module LeiosDemoLogic (module LeiosDemoLogic) where @@ -11,18 +12,27 @@ import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Monad (foldM, when) import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits +import Data.DList (DList) +import qualified Data.DList as DList import Data.Foldable (forM_) import Data.Functor ((<&>)) +import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (unfoldr) +import Data.Map (Map) import qualified Data.Map as Map +import Data.Sequence (Seq) +import qualified Data.Sequence as Seq +import Data.Set (Set) +import qualified Data.Set as Set import Data.String (fromString) import qualified Data.Vector as V import qualified Data.Vector.Mutable as MV import Data.Word (Word16, Word64) import qualified Database.SQLite3.Direct as DB import qualified LeiosDemoOnlyTestFetch as LF -import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosTx (..), TxHash (..)) +import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosOutstanding, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosFetchStaticEnv, LeiosTx (..), PeerId (..), TxHash (..)) +import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..)) import qualified LeiosDemoTypes as Leios ebIdSlot :: EbId -> SlotNo @@ -298,3 +308,263 @@ sql_retrieve_from_ebTxs = \WHERE x.txBytes IS NOT NULL\n\ \ORDER BY mem.txPoints.ebId ASC, mem.txPoints.txOffset ASC\n\ \" + +----- + +newtype LeiosFetchDecisions pid = + MkLeiosFetchDecisions + (Map (PeerId pid) (Map SlotNo (DList (TxHash, BytesSize, Map EbId Int), DList EbId))) + +emptyLeiosFetchDecisions :: LeiosFetchDecisions pid +emptyLeiosFetchDecisions = MkLeiosFetchDecisions Map.empty + +leiosFetchLogicIteration :: forall pid. + Ord pid + => + LeiosFetchStaticEnv + -> + (LeiosEbBodies, Map (PeerId pid) (Set EbId, Set EbId)) + -> + LeiosOutstanding pid + -> + (LeiosOutstanding pid, LeiosFetchDecisions pid) +leiosFetchLogicIteration env (ebBodies, offerings) = + \acc -> + go1 acc emptyLeiosFetchDecisions + $ expand + $ Map.toDescList + $ Map.map Left (Leios.missingEbBodies ebBodies) `Map.union` Map.map Right (Leios.missingEbTxs acc) + where + expand = \case + [] -> [] + (ebId, Left ebBytesSize):vs -> Left (ebId, ebBytesSize) : expand vs + (ebId, Right v):vs -> + [ Right (ebId, txOffset, txHash) | (txOffset, (txHash, _txBytesSize)) <- IntMap.toAscList v ] + <> expand vs + go1 !acc !accNew = \case + [] + -> (acc, accNew) + + Left (ebId, ebBytesSize) : targets + | let peerIds :: Set (PeerId pid) + peerIds = Map.findWithDefault Set.empty ebId (Leios.requestedEbPeers acc) + -> goEb2 acc accNew targets ebId ebBytesSize peerIds + + Right (ebId, txOffset, txHash) : targets + + | not $ Set.member txHash (Leios.missingTxBodies acc) -- we already have it + -> go1 acc accNew targets + + | Just _ <- Map.lookup ebId (Leios.toCopy acc) >>= IntMap.lookup txOffset + -- it's already scheduled to be copied from TxCache + -> go1 acc accNew targets + + | Just txBytesSize <- Map.lookup txHash (Leios.cachedTxs acc) -- it's in the TxCache + -> let full = + Leios.toCopyBytesSize acc >= Leios.maxToCopyBytesSize env + || + Leios.toCopyCount acc >= Leios.maxToCopyCount env + acc' = + if full then acc else + acc { + Leios.toCopy = Map.insertWith IntMap.union ebId (IntMap.singleton txOffset txBytesSize) (Leios.toCopy acc) + , + Leios.toCopyBytesSize = Leios.toCopyBytesSize acc + txBytesSize + , + Leios.toCopyCount = Leios.toCopyCount acc + 1 + } + in go1 acc' accNew targets + + | otherwise + -> let !txOffsets = case Map.lookup txHash (Leios.txOffsetss acc) of + Nothing -> error "impossible!" + Just x -> x + peerIds :: Set (PeerId pid) + peerIds = Map.findWithDefault Set.empty txHash (Leios.requestedTxPeers acc) + in + goTx2 acc accNew targets (ebIdSlot ebId) txHash txOffsets peerIds + + goEb2 !acc !accNew targets ebId ebBytesSize peerIds + | Leios.requestedBytesSize acc >= Leios.maxRequestedBytesSize env -- we can't request anything + = (acc, accNew) + + | Set.size peerIds < Leios.maxRequestsPerEb env -- we would like to request it from an additional peer + , Just peerId <- choosePeerEb peerIds acc ebId + -- there's a peer who offered it and we haven't already requested it from them + = let accNew' = + MkLeiosFetchDecisions + $ Map.insertWith + (Map.unionWith (<>)) + peerId + (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton ebId)) + (let MkLeiosFetchDecisions x = accNew in x) + acc' = acc { + Leios.requestedEbPeers = Map.insertWith Set.union ebId (Set.singleton peerId) (Leios.requestedEbPeers acc) + , + Leios.requestedBytesSizePerPeer = Map.insertWith (+) peerId ebBytesSize (Leios.requestedBytesSizePerPeer acc) + , + Leios.requestedBytesSize = ebBytesSize + Leios.requestedBytesSize acc + } + peerIds' = Set.insert peerId peerIds + in + goEb2 acc' accNew' targets ebId ebBytesSize peerIds' + + | otherwise + = go1 acc accNew targets + + choosePeerEb :: Set (PeerId pid) -> LeiosOutstanding pid -> EbId -> Maybe (PeerId pid) + choosePeerEb peerIds acc ebId = + foldr (\a _ -> Just a) Nothing + $ [ peerId + | (peerId, (ebIds, _ebIds)) <- + Map.toList -- TODO prioritize/shuffle? + $ (`Map.withoutKeys` peerIds) -- not already requested from this peer + $ offerings + , Map.findWithDefault 0 peerId (Leios.requestedBytesSizePerPeer acc) <= Leios.maxRequestedBytesSizePerPeer env + -- peer can be sent more requests + , ebId `Set.member` ebIds -- peer has offered this EB body + ] + + goTx2 !acc !accNew targets ebSlot txHash txOffsets peerIds + + | Leios.requestedBytesSize acc >= Leios.maxRequestedBytesSize env -- we can't request anything + = (acc, accNew) + + | Set.size peerIds < Leios.maxRequestsPerTx env -- we would like to request it from an additional peer + -- TODO if requests list priority, does this limit apply even if the + -- tx has only been requested at lower priorities? + , Just (peerId, txOffsets') <- choosePeerTx peerIds acc txOffsets + -- there's a peer who offered it and we haven't already requested it from them + = let txBytesSize = case Map.lookupMax txOffsets' of + Nothing -> error "impossible!" + Just (ebId, txOffset) -> case Map.lookup ebId (Leios.missingEbTxs acc) of + Nothing -> error "impossible!" + Just v -> case IntMap.lookup txOffset v of + Nothing -> error "impossible!" + Just (_txHash, x) -> x + accNew' = + MkLeiosFetchDecisions + $ Map.insertWith + (Map.unionWith (<>)) + peerId + (Map.singleton ebSlot (DList.singleton (txHash, txBytesSize, txOffsets'), DList.empty)) + (let MkLeiosFetchDecisions x = accNew in x) + acc' = acc { + Leios.requestedTxPeers = Map.insertWith Set.union txHash (Set.singleton peerId) (Leios.requestedTxPeers acc) + , + Leios.requestedBytesSizePerPeer = Map.insertWith (+) peerId txBytesSize (Leios.requestedBytesSizePerPeer acc) + , + Leios.requestedBytesSize = txBytesSize + Leios.requestedBytesSize acc + } + peerIds' = Set.insert peerId peerIds + in + goTx2 acc' accNew' targets ebSlot txHash txOffsets peerIds' + + | otherwise + = go1 acc accNew targets + + choosePeerTx :: Set (PeerId pid) -> LeiosOutstanding pid -> Map EbId Int -> Maybe (PeerId pid, Map EbId Int) + choosePeerTx peerIds acc txOffsets = + foldr (\a _ -> Just a) Nothing + $ [ (peerId, txOffsets') + | (peerId, (_ebIds, ebIds)) <- + Map.toList -- TODO prioritize/shuffle? + $ (`Map.withoutKeys` peerIds) -- not already requested from this peer + $ offerings + , Map.findWithDefault 0 peerId (Leios.requestedBytesSizePerPeer acc) <= Leios.maxRequestedBytesSizePerPeer env + -- peer can be sent more requests + , let txOffsets' = txOffsets `Map.restrictKeys` ebIds + , not $ Map.null txOffsets' -- peer has offered an EB closure that includes this tx + ] + +packRequests :: LeiosFetchStaticEnv -> LeiosEbBodies -> LeiosFetchDecisions pid -> Map (PeerId pid) (Seq LeiosFetchRequest) +packRequests env ebBodies = + \(MkLeiosFetchDecisions x) -> Map.map goPeer x + where + goPeer = + Map.foldlWithKey + (\acc prio (txs, ebs) -> goPrioTx prio txs <> goPrioEb prio ebs <> acc) + -- TODO priority within same slot? + Seq.empty + + goPrioEb _prio ebs = + DList.foldr (Seq.:<|) Seq.empty + $ DList.map + (\ebId -> case ebIdToPoint ebId ebBodies of + Nothing -> error "impossible!" + Just p -> LeiosBlockRequest $ MkLeiosBlockRequest p + ) + ebs + + goPrioTx _prio txs = + Map.foldlWithKey + (\acc ebId txs' -> + case ebIdToPoint ebId ebBodies of + Nothing -> error "impossible!" + Just p -> + goEb + {- prio -} + p + 0 + IntMap.empty + 0 + DList.empty + (IntMap.toAscList txs') + <> acc + ) + Seq.empty + -- group by EbId, sort by offset ascending + $ Map.fromListWith IntMap.union + $ [ (,) ebId $ IntMap.singleton txOffset (txHash, txBytesSize) + | (txHash, txBytesSize, txOffsets) <- DList.toList txs + -- TODO somewhat arbitrarily choosing the freshest EbId here; merely + -- something simple and sufficient for the demo + , let (ebId, txOffset) = + case Map.lookupMax txOffsets of + Nothing -> error "impossible!" + Just x -> x + ] + + goEb :: + LeiosPoint + -> + BytesSize + -> + IntMap Word64 + -> + Int + -> + DList TxHash + -> + [(Int, (TxHash, BytesSize))] + -> + Seq LeiosFetchRequest + -- TODO the incoming indexes are ascending, so the IntMap accumulator could + -- be simplified away + goEb p !accTxBytesSize !accBitmaps !accN !accHashes = \case + [] -> if 0 < accN then Seq.singleton flush else Seq.empty + (txOffset, (txHash, txBytesSize)):txs + + | Leios.maxRequestBytesSize env < accTxBytesSize' + -> flush Seq.:<| goEb p 0 IntMap.empty 0 DList.empty txs + + | otherwise + , let (q, r) = txOffset `divMod` 64 + -> goEb + p + accTxBytesSize' + (IntMap.insertWith (Bits..|.) q (Bits.bit (63 - r)) accBitmaps) + (accN + 1) + (accHashes `DList.snoc` txHash) + txs + + where + accTxBytesSize' = accTxBytesSize + txBytesSize + where + flush = + LeiosBlockTxsRequest + $ MkLeiosBlockTxsRequest + {- prio -} + p + [ (fromIntegral idx, bitmap) | (idx, bitmap) <- IntMap.toAscList accBitmaps ] + (V.fromListN accN $ DList.toList accHashes) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 0c16d672d5..dc92c50712 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -13,8 +13,8 @@ import qualified Codec.CBOR.Encoding as CBOR import Codec.Serialise (decode, encode) import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar -import Control.Concurrent.Class.MonadSTM (TVar) -import qualified Control.Concurrent.Class.MonadSTM as STM +import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) +import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Data.ByteString (ByteString) import Data.Int (Int64) import Data.IntMap (IntMap) @@ -74,19 +74,16 @@ data LeiosFetchRequest = LeiosBlockTxsRequest LeiosBlockTxsRequest data LeiosBlockRequest = - -- | ebSlot, ebHash MkLeiosBlockRequest - !SlotNo - !ByteString + !LeiosPoint data LeiosBlockTxsRequest = - -- | ebSlot, ebHash, bitmaps, txHashes + -- | -- -- The hashes aren't sent to the peer, but they are used to validate the -- reply when it arrives. MkLeiosBlockTxsRequest - !SlotNo - !ByteString + !LeiosPoint [(Word16, Word64)] !(V.Vector TxHash) @@ -118,13 +115,13 @@ data LeiosPeerVars m = MkLeiosPeerVars { -- -- This is a 'TVar' so that the LeiosFetch client can wait on either it or -- the Diffusion Layer's control message to be actionable. - requestsToSend :: !(TVar m (Seq LeiosFetchRequest)) + requestsToSend :: !(StrictTVar m (Seq LeiosFetchRequest)) } newLeiosPeerVars :: IOLike m => m (LeiosPeerVars m) newLeiosPeerVars = do offerings <- MVar.newMVar (Set.empty, Set.empty) - requestsToSend <- STM.newTVarIO Seq.empty + requestsToSend <- StrictSTM.newTVarIO Seq.empty pure MkLeiosPeerVars {offerings, requestsToSend} data LeiosEbBodies = MkLeiosEbBodies { @@ -161,10 +158,16 @@ data LeiosOutstanding pid = MkLeiosOutstanding { missingTxBodies :: !(Set TxHash) , -- TODO this is far too big for the heap - ebBodies :: !(Map EbId (IntMap (TxHash, BytesSize))) + missingEbTxs :: !(Map EbId (IntMap (TxHash, BytesSize))) , -- TODO this is far too big for the heap txOffsetss :: !(Map TxHash (Map EbId Int)) + , + toCopy :: !(Map EbId (IntMap BytesSize)) + , + toCopyBytesSize :: !BytesSize + , + toCopyCount :: !Int } emptyLeiosOutstanding :: LeiosOutstanding pid @@ -178,17 +181,9 @@ emptyLeiosOutstanding = Set.empty Map.empty Map.empty - -data LeiosToCopy = MkLeiosToCopy { - toCopy :: !(Map EbId (IntMap BytesSize)) - , - toCopyBytesSize :: !BytesSize - , - toCopyCount :: !Int - } - -emptyLeiosToCopy :: LeiosToCopy -emptyLeiosToCopy = MkLeiosToCopy Map.empty 0 0 + Map.empty + 0 + 0 ----- @@ -320,3 +315,55 @@ withDieDone io = withDie io >>= \case DB.Row -> die "impossible!" DB.Done -> pure () + +----- + +-- TODO which of these limits are allowed to be exceeded by at most one +-- request? +data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { + -- | At most this many outstanding bytes requested from all peers together + maxRequestedBytesSize :: BytesSize + , + -- | At most this many outstanding bytes requested from each peer + maxRequestedBytesSizePerPeer :: BytesSize + , + -- | At most this many outstanding bytes per request + maxRequestBytesSize :: BytesSize + , + -- | At most this many outstanding requests for each EB body + maxRequestsPerEb :: Int + , + -- | At most this many outstanding requests for each individual tx + maxRequestsPerTx :: Int + , + -- | At most this many bytes are scheduled to be copied from the TxCache to the EbStore + maxToCopyBytesSize :: BytesSize + , + -- | At most this many txs are scheduled to be copied from the TxCache to the EbStore + maxToCopyCount :: Int + } + +demoLeiosFetchStaticEnv :: LeiosFetchStaticEnv +demoLeiosFetchStaticEnv = + MkLeiosFetchStaticEnv { + maxRequestedBytesSize = 50 * million + , + maxRequestedBytesSizePerPeer = 5 * million + , + maxRequestBytesSize = 500 * thousand + , + maxRequestsPerEb = 2 + , + maxRequestsPerTx = 2 + , + maxToCopyBytesSize = 100 * millionBase2 + , + maxToCopyCount = 100 * thousand + } + where + million :: Num a => a + million = 10^(6 :: Int) + millionBase2 :: Num a => a + millionBase2 = 2^(20 :: Int) + thousand :: Num a => a + thousand = 10^(3 :: Int) From d8e11d7a324ebc12f0460a668f5eb70727535e32 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 13:34:58 -0700 Subject: [PATCH 090/119] leiosdemo202510: now sending LeiosFetch requests, but ignoring responses --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 29 ++++++++--- ouroboros-consensus/ouroboros-consensus.cabal | 1 + .../src/ouroboros-consensus/LeiosDemoLogic.hs | 52 ++++++++++++++++++- .../LeiosDemoOnlyTestFetch.hs | 10 ++-- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 23 +++++++- scripts/leios-demo/leios-october-demo.sh | 6 +-- 6 files changed, 104 insertions(+), 17 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 3a806dc67b..208be69339 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -348,14 +348,23 @@ mkHandlers ) , hLeiosNotifyServer = \_version _peer -> leiosNotifyServerPeer - (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO - , hLeiosFetchClient = \_version controlMessageSTM _peer -> - , hLeiosFetchClient = \_version controlMessageSTM _peer -> toLeiosFetchClientPeerPipelined $ - leiosFetchClientPeerPipelined - (pure $ Left $ atomically $ controlMessageSTM >>= \case - Terminate -> pure $ Left () - _ -> retry - ) + (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO step 5 + , hLeiosFetchClient = \_version controlMessageSTM peer -> toLeiosFetchClientPeerPipelined $ Effect $ do + reqVar <- + let loop = do + leiosPeersVars <- MVar.readMVar getLeiosPeersVars + case Map.lookup (Leios.MkPeerId peer) leiosPeersVars of + Just x -> pure $ Leios.requestsToSend x + Nothing -> do + -- TODO the LeiosNotify client has not inserted it yet + threadDelay (0.010 :: DiffTime) + loop + in loop + pure + $ leiosFetchClientPeerPipelined + $ Leios.nextLeiosFetchClientCommand + ((== Terminate) <$> controlMessageSTM) + reqVar , hLeiosFetchServer = \_version _peer -> Effect $ do Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection leiosFetchContext <- @@ -369,6 +378,10 @@ mkHandlers NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosReady} = nodeKernel + -- TODO step 3: actually store them in the database + -- + -- TODO step 4: actually execute the ToCopy + {------------------------------------------------------------------------------- Codecs -------------------------------------------------------------------------------} diff --git a/ouroboros-consensus/ouroboros-consensus.cabal b/ouroboros-consensus/ouroboros-consensus.cabal index 397b367bca..33927930f8 100644 --- a/ouroboros-consensus/ouroboros-consensus.cabal +++ b/ouroboros-consensus/ouroboros-consensus.cabal @@ -320,6 +320,7 @@ library deepseq, diff-containers >=1.2, direct-sqlite, + directory, dlist, filelock, fingertree-rm >=1.0, diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index b032a31d67..5fd90241cf 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -9,6 +9,8 @@ module LeiosDemoLogic (module LeiosDemoLogic) where import Cardano.Slotting.Slot (SlotNo (..)) import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) import qualified Control.Concurrent.Class.MonadMVar as MVar +import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) +import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Control.Monad (foldM, when) import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits @@ -30,6 +32,7 @@ import qualified Data.Vector as V import qualified Data.Vector.Mutable as MV import Data.Word (Word16, Word64) import qualified Database.SQLite3.Direct as DB +import Debug.Trace (traceM) import qualified LeiosDemoOnlyTestFetch as LF import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosOutstanding, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosFetchStaticEnv, LeiosTx (..), PeerId (..), TxHash (..)) import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..)) @@ -157,9 +160,11 @@ leiosFetchHandler :: -> LF.LeiosFetchRequestHandler LeiosPoint LeiosEb LeiosTx m leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case - LF.MsgLeiosBlockRequest p -> + LF.MsgLeiosBlockRequest p -> do + traceM $ "MsgLeiosBlockRequest " <> Leios.prettyLeiosPoint p LF.MsgLeiosBlock <$> msgLeiosBlockRequest leiosContext p - LF.MsgLeiosBlockTxsRequest p bitmaps -> + LF.MsgLeiosBlockTxsRequest p bitmaps -> do + traceM $ "MsgLeiosBlockTxsRequest " <> Leios.prettyLeiosPoint p LF.MsgLeiosBlockTxs <$> msgLeiosBlockTxsRequest leiosContext p bitmaps msgLeiosBlockRequest :: PrimMonad m => LeiosFetchContext stmt m -> LeiosPoint -> m LeiosEb @@ -568,3 +573,46 @@ packRequests env ebBodies = p [ (fromIntegral idx, bitmap) | (idx, bitmap) <- IntMap.toAscList accBitmaps ] (V.fromListN accN $ DList.toList accHashes) + +----- + +nextLeiosFetchClientCommand :: forall eb tx m. + StrictSTM.MonadSTM m + => + StrictSTM.STM m Bool + -> + StrictTVar m (Seq LeiosFetchRequest) + -> + m (Either + (m (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m))) + (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m)) + ) +nextLeiosFetchClientCommand stopSTM reqsVar = do + f (pure Nothing) (pure . Just) >>= \case + Just x -> pure $ Right x + Nothing -> pure $ Left $ f StrictSTM.retry pure + where + f :: + StrictSTM.STM m r + -> + (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m) -> StrictSTM.STM m r) + -> + m r + f retry_ pure_ = StrictSTM.atomically $ do + stopSTM >>= \case + True -> pure_ $ Left () + False -> StrictSTM.readTVar reqsVar >>= \case + Seq.Empty -> retry_ + req Seq.:<| reqs -> do + StrictSTM.writeTVar reqsVar reqs + pure_ $ Right $ g req + + g = \case + LeiosBlockRequest (MkLeiosBlockRequest p) -> + LF.MkSomeLeiosFetchJob + (LF.MsgLeiosBlockRequest p) + (pure $ \_ -> pure ()) + LeiosBlockTxsRequest (MkLeiosBlockTxsRequest p bitmaps _txHashes) -> + LF.MkSomeLeiosFetchJob + (LF.MsgLeiosBlockTxsRequest p bitmaps) + (pure $ \_ -> pure ()) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs index 2de0496310..a977e19d27 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoOnlyTestFetch.hs @@ -27,6 +27,7 @@ module LeiosDemoOnlyTestFetch , LeiosFetchClientPeerPipelined , LeiosFetchServerPeer , LeiosFetchRequestHandler (..) + , SomeLeiosFetchJob (..) , leiosFetchClientPeer , leiosFetchClientPeerPipelined , leiosFetchServerPeer @@ -244,7 +245,7 @@ encodeLeiosFetch encodeP encodeEb encodeTx = encode -- MsgLeiosLastBlockAndTxsInRange MsgDone -> CBOR.encodeListLen 1 - <> CBOR.encodeWord 8 + <> CBOR.encodeWord 9 decodeLeiosFetch :: forall (point :: Type) (eb :: Type) (tx :: Type) @@ -268,7 +269,7 @@ decodeLeiosFetch decodeP decodeEb decodeTx = decode -> CBOR.Decoder s (SomeMessage st') decode stok len key = do case (stok, len, key) of - (SingIdle, 1, 0) -> do + (SingIdle, 2, 0) -> do p <- decodeP return $ SomeMessage $ MsgLeiosBlockRequest p (SingBlock, 2, 1) -> do @@ -467,7 +468,10 @@ leiosFetchClientPeerPipelined :: forall m point eb tx a. PrimMonad m => - m (Either (m (Either a (SomeLeiosFetchJob point eb tx m))) (Either a (SomeLeiosFetchJob point eb tx m))) + m (Either + (m (Either a (SomeLeiosFetchJob point eb tx m))) + (Either a (SomeLeiosFetchJob point eb tx m)) + ) -- ^ either the return value or the next job, or a blocking request for those two -> Peer (LeiosFetch point eb tx) AsClient (Pipelined Z C) StIdle m a diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index dc92c50712..b29e31b808 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -5,7 +5,7 @@ module LeiosDemoTypes (module LeiosDemoTypes) where import Cardano.Binary (enforceSize) -import Cardano.Slotting.Slot (SlotNo) +import Cardano.Slotting.Slot (SlotNo (SlotNo)) import Codec.CBOR.Decoding (Decoder) import qualified Codec.CBOR.Decoding as CBOR import Codec.CBOR.Encoding (Encoding) @@ -16,6 +16,8 @@ import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Data.ByteString (ByteString) +import qualified Data.ByteString.Base16 as BS16 +import qualified Data.ByteString.Char8 as BS8 import Data.Int (Int64) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap @@ -31,6 +33,8 @@ import Data.Word (Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB import Ouroboros.Consensus.Util (ShowProxy (..)) import Ouroboros.Consensus.Util.IOLike (IOLike) +import System.Directory (doesFileExist) +import System.Environment (lookupEnv) import System.Exit (die) type BytesSize = Word32 @@ -55,6 +59,10 @@ data LeiosPoint = MkLeiosPoint SlotNo EbHash instance ShowProxy LeiosPoint where showProxy _ = "LeiosPoint" +prettyLeiosPoint :: LeiosPoint -> String +prettyLeiosPoint (MkLeiosPoint (SlotNo slotNo) (MkEbHash bytes)) = + "(" ++ show slotNo ++ ", " ++ BS8.unpack (BS16.encode bytes) ++ ")" + encodeLeiosPoint :: LeiosPoint -> Encoding encodeLeiosPoint (MkLeiosPoint ebSlot (MkEbHash ebHash)) = CBOR.encodeListLen 2 @@ -318,6 +326,19 @@ withDieDone io = ----- +demoNewLeiosDbConnectionIO :: IO (SomeLeiosDb IO) +demoNewLeiosDbConnectionIO = do + dbPath <- lookupEnv "LEIOS_DB_PATH" >>= \case + Nothing -> die "You must define the LEIOS_DB_PATH variable for this demo." + Just x -> pure x + doesFileExist dbPath >>= \case + False -> die $ "No such LeiosDb file: " ++ dbPath + True -> do + db <- withDieMsg $ DB.open (fromString dbPath) + pure $ MkSomeLeiosDb $ leiosDbFromSqliteDirect db + +----- + -- TODO which of these limits are allowed to be exceeded by at most one -- request? data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index f2993bb8f6..34881a2baa 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -33,8 +33,8 @@ if [[ -z "${LEIOS_SCHEDULE}" ]]; then exit 1 fi -if [[ -z "${LEIOS_DB}" ]]; then - echo "Error: \${LEIOS_DB} must be the path to an exist Leios database." >&2 +if [[ -z "${LEIOS_UPSTREAM_DB_PATH}" ]]; then + echo "Error: \${LEIOS_UPSTREAM_DB_PATH} must be the path to the source Leios database." >&2 exit 1 fi @@ -171,7 +171,7 @@ IMMDB_CMD_CORE="${IMMDB_SERVER} \ --initial-slot $REF_SLOT \ --initial-time $ONSET_OF_REF_SLOT --leios-schedule $LEIOS_SCHEDULE - --leios-db $LEIOS_DB + --leios-db $LEIOS_UPSTREAM_DB_PATH --port ${PORT1}" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" From 3a1e330b5e9e501d03333dfa90a1047b944e2c9b Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 15:22:45 -0700 Subject: [PATCH 091/119] leiosdemo202510: update model exe EB codec to match --- ouroboros-consensus/app/leiosdemo202510.hs | 73 +++++++++------------- 1 file changed, 28 insertions(+), 45 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 5de8e99f4e..0c3dd29ff1 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -306,7 +306,7 @@ generateDb prng0 db ebRecipes = do ebHash = Hash.castHash $ Hash.hashWithSerialiser - (encodeEB (fromIntegral . BS.length) (\(MkHashBytes x) -> x)) + (encodeEB (V.length txs) (fromIntegral . BS.length) (\(MkHashBytes x) -> x)) txs let (ebId, mbDynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv withDieMsg $ DB.exec db (fromString "BEGIN") @@ -441,28 +441,15 @@ encodeEbPair bytesToLen hashToBytes (txBytes, txHash) = CBOR.encodeBytes (hashToBytes txHash) <> CBOR.encodeWord16 (bytesToLen txBytes) -encodeEB :: Foldable f => (b -> Word16) -> (h -> ByteString) -> f (b, h) -> CBOR.Encoding -encodeEB bytesToLen hashToBytes ebPairs = - CBOR.encodeMapLenIndef - <> foldr - (\x r -> encodeEbPair bytesToLen hashToBytes x <> r) - CBOR.encodeBreak - ebPairs +encodeEB :: Foldable f => Int -> (b -> Word16) -> (h -> ByteString) -> f (b, h) -> CBOR.Encoding +encodeEB n bytesToLen hashToBytes ebPairs = + CBOR.encodeMapLen (fromIntegral n) + <> foldMap (encodeEbPair bytesToLen hashToBytes) ebPairs decodeEbPair :: CBOR.Decoder s (ByteString, Word16) decodeEbPair = (,) <$> CBOR.decodeBytes <*> CBOR.decodeWord16 --- | The logic in this module instead does this decoding incrementally -_decodeEB :: CBOR.Decoder s (X (ByteString, Word16)) -_decodeEB = - CBOR.decodeMapLenIndef - *> CBOR.decodeSequenceLenIndef - pushX - emptyX - id - decodeEbPair - ----- -- | helper for msgLeiosBlockRequest and msgLeiosBlockTxsRequest @@ -492,27 +479,30 @@ msgLeiosBlockRequest db ebId = do -- get the EB items stmt <- withDieJust $ DB.prepare db (fromString sql_lookup_ebBodies_DESC) withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) - let loop !acc = + let loop !accN !acc = withDie (DB.stepNoCB stmt) >>= \case - DB.Done -> pure acc + DB.Done -> pure (accN, acc) DB.Row -> do -- TODO use a sink buffer to avoid polluting the heap with these temporary copies? - txHashBytes <- DB.columnBlob stmt 0 - txBytesSize <- DB.columnInt64 stmt 1 - loop $ pushX acc (txBytesSize, txHashBytes) - acc <- loop emptyX + txOffset <- DB.columnInt64 stmt 0 + txHashBytes <- DB.columnBlob stmt 1 + txBytesSize <- DB.columnInt64 stmt 2 + loop + (if 0 == accN then fromIntegral (txOffset + 1) else accN) + (pushX acc (txBytesSize, txHashBytes)) + (n, acc) <- loop 0 emptyX -- combine the EB items BS.putStr $ BS16.encode $ serialize' - $ encodeEB fromIntegral id acc + $ encodeEB n fromIntegral id acc putStrLn "" -- | It's DESCending because the accumulator within the 'msgLeiosBlockRequest' -- logic naturally reverses it sql_lookup_ebBodies_DESC :: String sql_lookup_ebBodies_DESC = - "SELECT txHashBytes, txBytesSize FROM ebTxs\n\ + "SELECT txOffset, txHashBytes, txBytesSize FROM ebTxs\n\ \WHERE ebId = ?\n\ \ORDER BY txOffset DESC\n\ \" @@ -650,28 +640,21 @@ msgLeiosBlock db lfst0 peerId ebPath = do when (ebHash /= ebHash'') $ do die $ "MsgLeiosBlock hash mismatch: " <> show (ebHash, ebHash'') ebId <- ebIdFromPoint' db ebSlot (let MkHashBytes x = ebHash in x) - stmt_write_ebBodies <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) + stmt <- withDieJust $ DB.prepare db (fromString sql_insert_ebBody) withDieMsg $ DB.exec db (fromString "BEGIN") -- decode incrementally and simultaneously INSERT INTO ebTxs - withDie $ DB.bindInt64 stmt_write_ebBodies 1 (fromIntegralEbId ebId) - let decodeBreakOrEbPair = do - stop <- CBOR.decodeBreakOr - if stop then pure Nothing else Just <$> decodeEbPair - let go1 txOffset bytes = do - (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeBreakOrEbPair bytes + withDie $ DB.bindInt64 stmt 1 (fromIntegralEbId ebId) + (ebBytes2, n) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeMapLen $ BSL.fromStrict ebBytes + let go1 txOffset bytes = if fromIntegral n == txOffset then pure () else do + (bytes', next) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes decodeEbPair bytes go2 txOffset bytes' next - go2 txOffset bytes = \case - Just (txHashBytes, txBytesSize) -> do - withDie $ DB.bindInt64 stmt_write_ebBodies 2 txOffset - withDie $ DB.bindBlob stmt_write_ebBodies 3 txHashBytes - withDie $ DB.bindInt64 stmt_write_ebBodies 4 (fromIntegral txBytesSize) - withDieDone $ DB.stepNoCB stmt_write_ebBodies - withDie $ DB.reset stmt_write_ebBodies - go1 (txOffset + 1) bytes - Nothing - | not (BSL.null bytes) -> die "Incomplete EB decode" - | otherwise -> pure () - (ebBytes2, ()) <- withDiePoly id $ pure $ CBOR.deserialiseFromBytes CBOR.decodeMapLenIndef $ BSL.fromStrict ebBytes + go2 txOffset bytes (txHashBytes, txBytesSize) = do + withDie $ DB.bindInt64 stmt 2 txOffset + withDie $ DB.bindBlob stmt 3 txHashBytes + withDie $ DB.bindInt64 stmt 4 (fromIntegral txBytesSize) + withDieDone $ DB.stepNoCB stmt + withDie $ DB.reset stmt + go1 (txOffset + 1) bytes go1 0 ebBytes2 -- finalize the EB withDieMsg $ DB.exec db (fromString "COMMIT") From 4f7c88c91ba5ed6a675b37cbaed31c29ac14653e Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 16:45:20 -0700 Subject: [PATCH 092/119] leiosdemo202510: now processing MsgLeiosBlock, but ignoring MsgLeiosBlockTxs --- .../ouroboros-consensus-cardano.cabal | 1 - .../Cardano/Tools/ImmDBServer/Diffusion.hs | 6 +- .../Ouroboros/Consensus/Network/NodeToNode.hs | 16 +- .../Ouroboros/Consensus/NodeKernel.hs | 11 +- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 195 +++++++++++++++--- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 32 ++- 6 files changed, 206 insertions(+), 55 deletions(-) diff --git a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal index 7e2fb3e230..a4e5a03584 100644 --- a/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal +++ b/ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal @@ -563,7 +563,6 @@ library unstable-cardano-tools compact, containers >=0.5 && <0.8, contra-tracer, - direct-sqlite, directory, dot, filepath, diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index ae39d30017..5117240995 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -18,12 +18,10 @@ import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Lazy as BL import Data.Functor.Contravariant ((>$<)) import qualified Data.Map.Strict as Map -import Data.String (fromString) import qualified Data.Text as T import qualified Data.Text.Encoding as T import Data.Void (Void) import Data.Word (Word32, Word64) -import qualified Database.SQLite3.Direct as DB import GHC.Generics (Generic) import qualified Network.Mux as Mux import Network.Socket (SockAddr (..)) @@ -117,9 +115,7 @@ run immDBDir sockAddr cfg getSlotDelay leiosDbFile leiosSchedule = withRegistry Dir.doesFileExist leiosDbFile >>= \case False -> die $ "The Leios database must already exist: " <> show leiosDbFile True -> pure () - leiosDb <- DB.open (fromString leiosDbFile) >>= \case - Left (_err, utf8) -> die $ show utf8 - Right x -> pure $ Leios.leiosDbFromSqliteDirect x + Leios.MkSomeLeiosDb leiosDb <- Leios.newLeiosDbConnectionIO leiosDbFile leiosEbBodies <- LeiosLogic.loadEbBodies leiosDb fmap LeiosLogic.MkSomeLeiosFetchContext $ LeiosLogic.newLeiosFetchContext diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 208be69339..c51dfe1d08 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -143,6 +143,8 @@ import qualified LeiosDemoTypes as Leios import qualified LeiosDemoLogic as Leios import qualified Ouroboros.Network.Mux as ON +import Debug.Trace (traceM) + {------------------------------------------------------------------------------- Handlers -------------------------------------------------------------------------------} @@ -315,6 +317,7 @@ mkHandlers (pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do + traceM $ "MsgLeiosBlockOffer " <> Leios.prettyLeiosPoint p ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do let (ebId, mbEbBodies2) = Leios.ebIdFromPoint p ebBodies1 ebBodies2 = fromMaybe ebBodies1 mbEbBodies2 @@ -335,6 +338,7 @@ mkHandlers pure (offers1', offers2) void $ MVar.tryPutMVar getLeiosReady () MsgLeiosBlockTxsOffer p -> do + traceM $ "MsgLeiosBlockTxsOffer " <> Leios.prettyLeiosPoint p ebId <- Leios.ebIdFromPointM getLeiosEbBodies p peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars @@ -348,8 +352,9 @@ mkHandlers ) , hLeiosNotifyServer = \_version _peer -> leiosNotifyServerPeer - (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO step 5 + (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO , hLeiosFetchClient = \_version controlMessageSTM peer -> toLeiosFetchClientPeerPipelined $ Effect $ do + Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection -- TODO share DB connection for same peer? reqVar <- let loop = do leiosPeersVars <- MVar.readMVar getLeiosPeersVars @@ -364,6 +369,9 @@ mkHandlers $ leiosFetchClientPeerPipelined $ Leios.nextLeiosFetchClientCommand ((== Terminate) <$> controlMessageSTM) + (getLeiosEbBodies, getLeiosOutstanding, getLeiosReady) + db + (Leios.MkPeerId peer) reqVar , hLeiosFetchServer = \_version _peer -> Effect $ do Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection @@ -376,11 +384,7 @@ mkHandlers } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel - NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosReady} = nodeKernel - - -- TODO step 3: actually store them in the database - -- - -- TODO step 4: actually execute the ToCopy + NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index dfcf220ded..13d3837da4 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -136,6 +136,8 @@ import LeiosDemoTypes (LeiosEbBodies, LeiosOutstanding, LeiosPeerVars, import qualified LeiosDemoTypes as Leios import qualified LeiosDemoLogic as Leios +import Debug.Trace (traceM) + {------------------------------------------------------------------------------- Relay node -------------------------------------------------------------------------------} @@ -368,8 +370,8 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers let getLeiosNewDbConnection = nkaGetLeiosNewDbConnection getLeiosPeersVars <- MVar.newMVar Map.empty - getLeiosEbBodies <- MVar.newMVar Leios.emptyLeiosEbBodies - getLeiosOutstanding <- MVar.newMVar Leios.emptyLeiosOutstanding + getLeiosEbBodies <- MVar.newMVar Leios.emptyLeiosEbBodies -- TODO init from DB + getLeiosOutstanding <- MVar.newMVar Leios.emptyLeiosOutstanding -- TODO init from DB getLeiosReady <- MVar.newEmptyMVar void $ forkLinkedThread registry "NodeKernel.leiosFetchLogic" $ forever $ do @@ -383,10 +385,13 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers (ebBodies, offerings) outstanding let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions + traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs" (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> atomically $ do StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) - threadDelay (0.050 :: DiffTime) -- TODO magic number + threadDelay (1 :: DiffTime) -- TODO magic number + + -- TODO Leios.toCopy return NodeKernel { getChainDB = chainDB diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 5fd90241cf..0e122e1302 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -3,21 +3,27 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} module LeiosDemoLogic (module LeiosDemoLogic) where +import Cardano.Binary (serialize') +import qualified Cardano.Crypto.Hash as Hash import Cardano.Slotting.Slot (SlotNo (..)) import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) import qualified Control.Concurrent.Class.MonadMVar as MVar +import Control.Concurrent.Class.MonadSTM (MonadSTM) import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Control.Monad (foldM, when) import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits +import Data.ByteString (ByteString) +import qualified Data.ByteString as BS import Data.DList (DList) import qualified Data.DList as DList import Data.Foldable (forM_) -import Data.Functor ((<&>)) +import Data.Functor ((<&>), void) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.List (unfoldr) @@ -38,6 +44,8 @@ import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodie import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..)) import qualified LeiosDemoTypes as Leios +type HASH = Hash.Blake2b_256 + ebIdSlot :: EbId -> SlotNo ebIdSlot (MkEbId y) = SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) @@ -233,7 +241,6 @@ msgLeiosBlockTxsRequest leiosContext p bitmaps = do Just (64 * fromIntegral idx + i, (idx, bitmap') : k) txOffsets = unfoldr nextOffset bitmaps -- fill in-memory table - dbExec db (fromString sql_attach_memTxPoints) dbExec db (fromString "BEGIN") do stmt <- dbPrepare db (fromString sql_insert_memTxPoints) @@ -257,8 +264,8 @@ msgLeiosBlockTxsRequest leiosContext p bitmaps = do error $ "Missing offset " ++ show (txOffset, txOffset') MV.write buf i (MkLeiosTx txBytes) pure $! (i + 1) + dbExec db (fromString sql_flush_memTxPoints) dbExec db (fromString "COMMIT") - dbExec db (fromString sql_detach_memTxPoints) V.freeze $ MV.slice 0 n buf {- | For example @@ -281,25 +288,17 @@ popLeftmostOffset = \case in Just (zs, Bits.clearBit w (63 - zs)) -sql_attach_memTxPoints :: String -sql_attach_memTxPoints = - "ATTACH DATABASE ':memory:' AS mem;\n\ - \\n\ - \CREATE TABLE mem.txPoints (\n\ - \ ebId INTEGER NOT NULL\n\ - \ ,\n\ - \ txOffset INTEGER NOT NULL\n\ - \ ,\n\ - \ PRIMARY KEY (ebId ASC, txOffset ASC)\n\ - \ ) WITHOUT ROWID;\n\ - \" - -sql_detach_memTxPoints :: String -sql_detach_memTxPoints = +_sql_detach_memTxPoints :: String +_sql_detach_memTxPoints = -- NB :memory: databases are discarded when detached "DETACH DATABASE mem;\n\ \" +sql_flush_memTxPoints :: String +sql_flush_memTxPoints = + "DELETE FROM mem.txPoints;\n\ + \" + sql_insert_memTxPoints :: String sql_insert_memTxPoints = "INSERT INTO mem.txPoints (ebId, txOffset) VALUES (?, ?);\n\ @@ -318,7 +317,7 @@ sql_retrieve_from_ebTxs = newtype LeiosFetchDecisions pid = MkLeiosFetchDecisions - (Map (PeerId pid) (Map SlotNo (DList (TxHash, BytesSize, Map EbId Int), DList EbId))) + (Map (PeerId pid) (Map SlotNo (DList (TxHash, BytesSize, Map EbId Int), DList (EbId , BytesSize)))) emptyLeiosFetchDecisions :: LeiosFetchDecisions pid emptyLeiosFetchDecisions = MkLeiosFetchDecisions Map.empty @@ -357,9 +356,6 @@ leiosFetchLogicIteration env (ebBodies, offerings) = Right (ebId, txOffset, txHash) : targets - | not $ Set.member txHash (Leios.missingTxBodies acc) -- we already have it - -> go1 acc accNew targets - | Just _ <- Map.lookup ebId (Leios.toCopy acc) >>= IntMap.lookup txOffset -- it's already scheduled to be copied from TxCache -> go1 acc accNew targets @@ -401,7 +397,7 @@ leiosFetchLogicIteration env (ebBodies, offerings) = $ Map.insertWith (Map.unionWith (<>)) peerId - (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton ebId)) + (Map.singleton (ebIdSlot ebId) (DList.empty, DList.singleton (ebId, ebBytesSize))) (let MkLeiosFetchDecisions x = accNew in x) acc' = acc { Leios.requestedEbPeers = Map.insertWith Set.union ebId (Set.singleton peerId) (Leios.requestedEbPeers acc) @@ -495,9 +491,9 @@ packRequests env ebBodies = goPrioEb _prio ebs = DList.foldr (Seq.:<|) Seq.empty $ DList.map - (\ebId -> case ebIdToPoint ebId ebBodies of + (\(ebId, ebBytesSize) -> case ebIdToPoint ebId ebBodies of Nothing -> error "impossible!" - Just p -> LeiosBlockRequest $ MkLeiosBlockRequest p + Just p -> LeiosBlockRequest $ MkLeiosBlockRequest p ebBytesSize ) ebs @@ -576,18 +572,30 @@ packRequests env ebBodies = ----- -nextLeiosFetchClientCommand :: forall eb tx m. - StrictSTM.MonadSTM m +nextLeiosFetchClientCommand :: forall pid tx stmt m. + ( + Ord pid + , + MonadSTM m + , + MonadMVar m + ) => StrictSTM.STM m Bool + -> + (MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + -> + LeiosDb stmt m + -> + PeerId pid -> StrictTVar m (Seq LeiosFetchRequest) -> m (Either - (m (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m))) - (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m)) + (m (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m))) + (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m)) ) -nextLeiosFetchClientCommand stopSTM reqsVar = do +nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do f (pure Nothing) (pure . Just) >>= \case Just x -> pure $ Right x Nothing -> pure $ Left $ f StrictSTM.retry pure @@ -595,7 +603,7 @@ nextLeiosFetchClientCommand stopSTM reqsVar = do f :: StrictSTM.STM m r -> - (Either () (LF.SomeLeiosFetchJob LeiosPoint eb tx m) -> StrictSTM.STM m r) + (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m) -> StrictSTM.STM m r) -> m r f retry_ pure_ = StrictSTM.atomically $ do @@ -608,11 +616,130 @@ nextLeiosFetchClientCommand stopSTM reqsVar = do pure_ $ Right $ g req g = \case - LeiosBlockRequest (MkLeiosBlockRequest p) -> + LeiosBlockRequest req@(MkLeiosBlockRequest p _ebBytesSize) -> LF.MkSomeLeiosFetchJob (LF.MsgLeiosBlockRequest p) - (pure $ \_ -> pure ()) + (pure $ \(LF.MsgLeiosBlock eb) -> + msgLeiosBlock kernelVars db peerId req eb + ) LeiosBlockTxsRequest (MkLeiosBlockTxsRequest p bitmaps _txHashes) -> LF.MkSomeLeiosFetchJob (LF.MsgLeiosBlockTxsRequest p bitmaps) - (pure $ \_ -> pure ()) + (pure $ \(LF.MsgLeiosBlockTxs _txs) -> do + traceM $ "MsgLeiosBlockTxs " <> Leios.prettyLeiosPoint p + ) + +----- + +msgLeiosBlock :: + ( + Ord pid + , + MonadMVar m + ) + => + (MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + -> + LeiosDb stmt m + -> + PeerId pid + -> + LeiosBlockRequest + -> + LeiosEb + -> + m () +msgLeiosBlock (ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do + -- validate it + let MkLeiosBlockRequest p ebBytesSize = req + traceM $ "MsgLeiosBlock " <> Leios.prettyLeiosPoint p + do + let MkLeiosPoint _ebSlot ebHash = p + let ebBytes :: ByteString + ebBytes = serialize' $ Leios.encodeLeiosEb eb + let ebBytesSize' = BS.length ebBytes + when (ebBytesSize' /= fromIntegral ebBytesSize) $ do + error $ "MsgLeiosBlock size mismatch: " <> show (ebBytesSize', ebBytesSize) + let ebHash' :: EbHash + ebHash' = MkEbHash $ Hash.hashToBytes $ Hash.hashWith @HASH id ebBytes + when (ebHash' /= ebHash) $ do + error $ "MsgLeiosBlock hash mismatch: " <> show (ebHash', ebHash) + -- ingest it + (ebId, novel) <- MVar.modifyMVar ebBodiesVar $ \ebBodies -> do + ebId <- do + let (x, mbLeiosEbBodies') = ebIdFromPoint p ebBodies + case mbLeiosEbBodies' of + Just _ -> error "Unrecognized Leios point" + Nothing -> pure x + let novel = not $ Set.member ebId (Leios.acquiredEbBodies ebBodies) + when novel $ do -- TODO don't hold the mvar during this IO + stmt <- dbPrepare db (fromString sql_insert_ebBody) + dbExec db (fromString "BEGIN") + -- INSERT INTO ebTxs + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + V.iforM_ (let MkLeiosEb v = eb in v) $ \txOffset (txHash, txBytesSize) -> do + dbBindInt64 db stmt 2 (fromIntegral txOffset) + dbBindBlob db stmt 3 (let MkTxHash bytes = txHash in bytes) + dbBindInt64 db stmt 4 (fromIntegral txBytesSize) + dbStep1 db stmt + dbReset db stmt + dbFinalize db stmt + dbExec db (fromString "COMMIT") + -- update NodeKernel state + let !ebBodies' = if not novel then ebBodies else ebBodies { + Leios.acquiredEbBodies = Set.insert ebId (Leios.acquiredEbBodies ebBodies) + , + Leios.missingEbBodies = Map.delete ebId (Leios.missingEbBodies ebBodies) + } + pure (ebBodies', (ebId, novel)) + MVar.modifyMVar_ outstandingVar $ \outstanding -> do + let !outstanding' = outstanding { + Leios.missingEbTxs = + if not novel then Leios.missingEbTxs outstanding else + Map.insert + ebId + (V.ifoldl + (\acc i x -> IntMap.insert i x acc) + IntMap.empty + (let MkLeiosEb v = eb in v) + ) + (Leios.missingEbTxs outstanding) + , + Leios.txOffsetss = + if not novel then Leios.txOffsetss outstanding else + V.ifoldl + (\acc i (txHash, _txBytesSize) -> + Map.insertWith Map.union txHash (Map.singleton ebId i) acc + ) + (Leios.txOffsetss outstanding) + (let MkLeiosEb v = eb in v) + , + Leios.requestedBytesSize = Leios.requestedBytesSize outstanding - ebBytesSize + , + Leios.requestedBytesSizePerPeer = + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIfZero $ x - ebBytesSize + ) + peerId + (Leios.requestedBytesSizePerPeer outstanding) + , + Leios.requestedEbPeers = + Map.update (delIfNull . Set.delete peerId) ebId (Leios.requestedEbPeers outstanding) + } + pure outstanding' + void $ MVar.tryPutMVar readyVar () + +sql_insert_ebBody :: String +sql_insert_ebBody = + "INSERT INTO ebTxs (ebId, txOffset, txHashBytes, txBytesSize, txBytes) VALUES (?, ?, ?, ?, NULL)\n\ + \" + +----- + +delIfNull :: Set a -> Maybe (Set a) +delIfNull x = if Set.null x then Nothing else Just x + +delIfZero :: (Eq a, Num a) => a -> Maybe a +delIfZero x = if 0 == x then Nothing else Just x diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index b29e31b808..f481956634 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -82,14 +82,19 @@ data LeiosFetchRequest = LeiosBlockTxsRequest LeiosBlockTxsRequest data LeiosBlockRequest = + -- | + -- + -- The size isn't sent to the peer, but it's used to validate the reponse + -- when it arrives. MkLeiosBlockRequest !LeiosPoint + !BytesSize data LeiosBlockTxsRequest = -- | -- -- The hashes aren't sent to the peer, but they are used to validate the - -- reply when it arrives. + -- response when it arrives. MkLeiosBlockTxsRequest !LeiosPoint [(Word16, Word64)] @@ -161,9 +166,6 @@ data LeiosOutstanding pid = MkLeiosOutstanding { , -- TODO this might be far too big for the heap cachedTxs :: !(Map TxHash BytesSize) - , - -- TODO this is far too big for the heap - missingTxBodies :: !(Set TxHash) , -- TODO this is far too big for the heap missingEbTxs :: !(Map EbId (IntMap (TxHash, BytesSize))) @@ -186,7 +188,6 @@ emptyLeiosOutstanding = Map.empty 0 Map.empty - Set.empty Map.empty Map.empty Map.empty @@ -331,11 +332,30 @@ demoNewLeiosDbConnectionIO = do dbPath <- lookupEnv "LEIOS_DB_PATH" >>= \case Nothing -> die "You must define the LEIOS_DB_PATH variable for this demo." Just x -> pure x + newLeiosDbConnectionIO dbPath + +newLeiosDbConnectionIO :: FilePath -> IO (SomeLeiosDb IO) +newLeiosDbConnectionIO dbPath = do doesFileExist dbPath >>= \case False -> die $ "No such LeiosDb file: " ++ dbPath True -> do db <- withDieMsg $ DB.open (fromString dbPath) - pure $ MkSomeLeiosDb $ leiosDbFromSqliteDirect db + let db' = leiosDbFromSqliteDirect db + dbExec db' (fromString sql_attach_memTxPoints) + pure $ MkSomeLeiosDb db' + +sql_attach_memTxPoints :: String +sql_attach_memTxPoints = + "ATTACH DATABASE ':memory:' AS mem;\n\ + \\n\ + \CREATE TABLE mem.txPoints (\n\ + \ ebId INTEGER NOT NULL\n\ + \ ,\n\ + \ txOffset INTEGER NOT NULL\n\ + \ ,\n\ + \ PRIMARY KEY (ebId ASC, txOffset ASC)\n\ + \ ) WITHOUT ROWID;\n\ + \" ----- From 805756277fa3b08ae4ef397a6ee255e3c3ce413d Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 21:38:01 -0700 Subject: [PATCH 093/119] WIP one minute copies --- .../Tools/ImmDBServer/MiniProtocols.hs | 2 +- .../Ouroboros/Consensus/Network/NodeToNode.hs | 5 +- .../Ouroboros/Consensus/NodeKernel.hs | 48 ++- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 295 ++++++++++++++++-- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 61 +++- 5 files changed, 375 insertions(+), 36 deletions(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs index b1db39b3f5..6006c49203 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/MiniProtocols.hs @@ -243,7 +243,7 @@ chainSyncServer immDB blockComponent getSlotDelay registry = ChainSyncServer $ d ImmutableDB.iteratorNext iterator >>= \case ImmutableDB.IteratorExhausted -> do ImmutableDB.iteratorClose iterator - threadDelay (5 :: DiffTime) + threadDelay (1000 :: DiffTime) throwIO ReachedImmutableTip ImmutableDB.IteratorResult a -> do -- Wait until the slot of the current block has been reached diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index c51dfe1d08..b745e04d4b 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -328,6 +328,7 @@ mkHandlers Map.insert ebId ebBytesSize (Leios.missingEbBodies ebBodies2) } pure (ebBodies3, ebId) + traceM $ "leiosId: " ++ Leios.prettyLeiosPoint p ++ " ---> " ++ show (let Leios.MkEbId i = ebId in i) peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars case Map.lookup (Leios.MkPeerId peer) peersVars of @@ -369,7 +370,7 @@ mkHandlers $ leiosFetchClientPeerPipelined $ Leios.nextLeiosFetchClientCommand ((== Terminate) <$> controlMessageSTM) - (getLeiosEbBodies, getLeiosOutstanding, getLeiosReady) + (getLeiosWriteLock, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady) db (Leios.MkPeerId peer) reqVar @@ -384,7 +385,7 @@ mkHandlers } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel - NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady} = nodeKernel + NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady, getLeiosWriteLock} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 13d3837da4..4e03d2afc9 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -36,6 +36,7 @@ import qualified Control.Concurrent.Class.MonadSTM as LazySTM import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Control.DeepSeq (force) import Control.Monad +import Control.Monad.Class.MonadTime (getMonotonicTimeNSec) import qualified Control.Monad.Class.MonadTimer.SI as SI import Control.Monad.Except import Control.ResourceRegistry @@ -212,6 +213,12 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- 'MVar.tryPutMVar' whenever they make a change that might unblock a new -- fetch decision. , getLeiosReady :: MVar m () + -- | Must be held before writing to the database + -- + -- Preferable to dealing with SQLite's BUSY errors. + -- + -- INVARIANT: never acquire 'MVar' while holding this lock. + , getLeiosWriteLock :: MVar m () } @@ -373,25 +380,47 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers getLeiosEbBodies <- MVar.newMVar Leios.emptyLeiosEbBodies -- TODO init from DB getLeiosOutstanding <- MVar.newMVar Leios.emptyLeiosOutstanding -- TODO init from DB getLeiosReady <- MVar.newEmptyMVar + getLeiosWriteLock <- MVar.newMVar () + + getLeiosCopyReady <- MVar.newEmptyMVar void $ forkLinkedThread registry "NodeKernel.leiosFetchLogic" $ forever $ do () <- MVar.takeMVar getLeiosReady leiosPeersVars <- MVar.readMVar getLeiosPeersVars offerings <- mapM (MVar.readMVar . Leios.offerings) leiosPeersVars ebBodies <- MVar.readMVar getLeiosEbBodies - newDecisions <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do - pure $ Leios.leiosFetchLogicIteration - Leios.demoLeiosFetchStaticEnv - (ebBodies, offerings) - outstanding + (newDecisions, newCopy, xxx, yyy) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do + let (!outstanding', newDecisions) = + Leios.leiosFetchLogicIteration + Leios.demoLeiosFetchStaticEnv + (ebBodies, offerings) + outstanding + let newCopy = Leios.toCopyCount outstanding' /= Leios.toCopyCount outstanding + pure (outstanding', (newDecisions, newCopy, outstanding, outstanding')) let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions - traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs" + traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" ++ "\n" ++ + "leiosOutstanding: " ++ Leios.prettyLeiosOutstanding xxx ++ "\n" ++ + "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> atomically $ do StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) - threadDelay (1 :: DiffTime) -- TODO magic number - - -- TODO Leios.toCopy + when newCopy $ void $ MVar.tryPutMVar getLeiosCopyReady () + threadDelay (0.5 :: DiffTime) -- TODO magic number + + void $ forkLinkedThread registry "NodeKernel.leiosCopyLogic" $ do + Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection + (\m -> let loop !i = do m i; loop (i+1 :: Int) in loop 0) $ \i -> do + () <- MVar.takeMVar getLeiosCopyReady + traceM $ "leiosCopy: running " ++ show i + t1 <- getMonotonicTimeNSec + moreTodo <- Leios.doCacheCopy db (getLeiosWriteLock, getLeiosOutstanding) (500 * 10^(3 :: Int)) -- TODO magic number + t2 <- getMonotonicTimeNSec + traceM $ "leiosCopy: done " ++ show (i, (t2 - t1) `div` (10^(6 :: Int))) + void $ MVar.tryPutMVar getLeiosReady () + when moreTodo $ do + traceM $ "leiosCopy: more " ++ show i + void $ MVar.tryPutMVar getLeiosCopyReady () + threadDelay (0.050 :: DiffTime) -- TODO magic number return NodeKernel { getChainDB = chainDB @@ -415,6 +444,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getLeiosEbBodies , getLeiosOutstanding , getLeiosReady + , getLeiosWriteLock } where blockForgingController :: InternalState m remotePeer localPeer blk diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 0e122e1302..f98c6da9e7 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -7,7 +7,7 @@ module LeiosDemoLogic (module LeiosDemoLogic) where -import Cardano.Binary (serialize') +import Cardano.Binary (decodeFullDecoder', serialize') import qualified Cardano.Crypto.Hash as Hash import Cardano.Slotting.Slot (SlotNo (..)) import Control.Concurrent.Class.MonadMVar (MVar, MonadMVar) @@ -16,6 +16,7 @@ import Control.Concurrent.Class.MonadSTM (MonadSTM) import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Control.Monad (foldM, when) +import Control.Monad.Class.MonadTime (MonadMonotonicTimeNSec, getMonotonicTimeNSec) import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits import Data.ByteString (ByteString) @@ -26,9 +27,11 @@ import Data.Foldable (forM_) import Data.Functor ((<&>), void) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap +import qualified Data.IntSet as IntSet import Data.List (unfoldr) import Data.Map (Map) import qualified Data.Map as Map +import qualified Data.Map.Merge.Strict as MapMerge import Data.Sequence (Seq) import qualified Data.Sequence as Seq import Data.Set (Set) @@ -262,7 +265,10 @@ msgLeiosBlockTxsRequest leiosContext p bitmaps = do txBytes <- dbColumnBlob db stmt 1 when (fromIntegral txOffset /= txOffset') $ do error $ "Missing offset " ++ show (txOffset, txOffset') - MV.write buf i (MkLeiosTx txBytes) + tx <- case decodeFullDecoder' (fromString "txBytes column") Leios.decodeLeiosTx txBytes of + Left err -> error $ "Failed to deserialize txBytes column: " ++ Leios.prettyLeiosPoint p ++ " " ++ show (txOffset', err) + Right tx -> pure tx + MV.write buf i tx pure $! (i + 1) dbExec db (fromString sql_flush_memTxPoints) dbExec db (fromString "COMMIT") @@ -368,7 +374,30 @@ leiosFetchLogicIteration env (ebBodies, offerings) = acc' = if full then acc else acc { - Leios.toCopy = Map.insertWith IntMap.union ebId (IntMap.singleton txOffset txBytesSize) (Leios.toCopy acc) + Leios.missingEbTxs = + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIf IntMap.null $ IntMap.delete txOffset x + ) + ebId + (Leios.missingEbTxs acc) + , + Leios.txOffsetss = + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIf Map.null $ Map.delete ebId x + ) + txHash + (Leios.txOffsetss acc) + , + Leios.toCopy = + Map.insertWith + IntMap.union + ebId + (IntMap.singleton txOffset (txHash, txBytesSize)) + (Leios.toCopy acc) , Leios.toCopyBytesSize = Leios.toCopyBytesSize acc + txBytesSize , @@ -572,7 +601,7 @@ packRequests env ebBodies = ----- -nextLeiosFetchClientCommand :: forall pid tx stmt m. +nextLeiosFetchClientCommand :: forall pid stmt m. ( Ord pid , @@ -583,7 +612,7 @@ nextLeiosFetchClientCommand :: forall pid tx stmt m. => StrictSTM.STM m Bool -> - (MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) -> LeiosDb stmt m -> @@ -592,8 +621,8 @@ nextLeiosFetchClientCommand :: forall pid tx stmt m. StrictTVar m (Seq LeiosFetchRequest) -> m (Either - (m (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m))) - (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m)) + (m (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb LeiosTx m))) + (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb LeiosTx m)) ) nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do f (pure Nothing) (pure . Just) >>= \case @@ -603,7 +632,7 @@ nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do f :: StrictSTM.STM m r -> - (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb tx m) -> StrictSTM.STM m r) + (Either () (LF.SomeLeiosFetchJob LeiosPoint LeiosEb LeiosTx m) -> StrictSTM.STM m r) -> m r f retry_ pure_ = StrictSTM.atomically $ do @@ -622,11 +651,11 @@ nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do (pure $ \(LF.MsgLeiosBlock eb) -> msgLeiosBlock kernelVars db peerId req eb ) - LeiosBlockTxsRequest (MkLeiosBlockTxsRequest p bitmaps _txHashes) -> + LeiosBlockTxsRequest req@(MkLeiosBlockTxsRequest p bitmaps _txHashes) -> LF.MkSomeLeiosFetchJob (LF.MsgLeiosBlockTxsRequest p bitmaps) - (pure $ \(LF.MsgLeiosBlockTxs _txs) -> do - traceM $ "MsgLeiosBlockTxs " <> Leios.prettyLeiosPoint p + (pure $ \(LF.MsgLeiosBlockTxs txs) -> do + msgLeiosBlockTxs kernelVars db peerId req txs ) ----- @@ -638,7 +667,7 @@ msgLeiosBlock :: MonadMVar m ) => - (MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) -> LeiosDb stmt m -> @@ -649,7 +678,7 @@ msgLeiosBlock :: LeiosEb -> m () -msgLeiosBlock (ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do +msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do -- validate it let MkLeiosBlockRequest p ebBytesSize = req traceM $ "MsgLeiosBlock " <> Leios.prettyLeiosPoint p @@ -672,7 +701,7 @@ msgLeiosBlock (ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do Just _ -> error "Unrecognized Leios point" Nothing -> pure x let novel = not $ Set.member ebId (Leios.acquiredEbBodies ebBodies) - when novel $ do -- TODO don't hold the mvar during this IO + when novel $ MVar.withMVar writeLock $ \() -> do -- TODO don't hold the ebBodies mvar during this IO stmt <- dbPrepare db (fromString sql_insert_ebBody) dbExec db (fromString "BEGIN") -- INSERT INTO ebTxs @@ -720,13 +749,13 @@ msgLeiosBlock (ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do Map.alter (\case Nothing -> error "impossible!" - Just x -> delIfZero $ x - ebBytesSize + Just x -> delIf (==0) $ x - ebBytesSize ) peerId (Leios.requestedBytesSizePerPeer outstanding) , Leios.requestedEbPeers = - Map.update (delIfNull . Set.delete peerId) ebId (Leios.requestedEbPeers outstanding) + Map.update (delIf Set.null . Set.delete peerId) ebId (Leios.requestedEbPeers outstanding) } pure outstanding' void $ MVar.tryPutMVar readyVar () @@ -738,8 +767,234 @@ sql_insert_ebBody = ----- -delIfNull :: Set a -> Maybe (Set a) -delIfNull x = if Set.null x then Nothing else Just x +delIf :: (a -> Bool) -> a -> Maybe a +delIf predicate x = if predicate x then Nothing else Just x -delIfZero :: (Eq a, Num a) => a -> Maybe a -delIfZero x = if 0 == x then Nothing else Just x +----- + +msgLeiosBlockTxs :: + ( + Ord pid + , + MonadMVar m + ) + => + (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + -> + LeiosDb stmt m + -> + PeerId pid + -> + LeiosBlockTxsRequest + -> + V.Vector LeiosTx + -> + m () +msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req txs = do + traceM $ Leios.prettyLeiosBlockTxsRequest req + -- validate it + let MkLeiosBlockTxsRequest p bitmaps txHashes = req + let txBytess :: V.Vector ByteString + txBytess = V.map (serialize' . Leios.encodeLeiosTx) txs + do + when (V.length txs /= V.length txHashes) $ do + error $ "MsgLeiosBlockTxs length mismatch: " ++ show (V.length txs, V.length txHashes) + let rehash :: ByteString -> Hash.Hash HASH ByteString + rehash = Hash.hashWith id + let txHashes' = V.map (MkTxHash . Hash.hashToBytes . rehash) txBytess + when (txHashes' /= txHashes) $ do + let mismatches = + V.toList + $ V.findIndices id + $ V.zipWith (/=) txHashes txHashes' + error $ "MsgLeiosBlockTxs hash mismatches: " ++ show mismatches + ebId <- do + ebBodies <- MVar.readMVar ebBodiesVar + let (x, mbLeiosEbBodies') = ebIdFromPoint p ebBodies + case mbLeiosEbBodies' of + Just _ -> error "Unrecognized Leios point" + Nothing -> pure x + let nextOffset = \case + [] -> Nothing + (idx, bitmap) : k -> case popLeftmostOffset bitmap of + Nothing -> nextOffset k + Just (i, bitmap') -> + Just (64 * fromIntegral idx + i, (idx, bitmap') : k) + offsets = unfoldr nextOffset bitmaps + -- ingest + MVar.withMVar writeLock $ \() -> do + stmtTxCache <- dbPrepare db (fromString sql_insert_txCache) + stmtEbTxs <- dbPrepare db (fromString sql_update_ebTx) + dbBindInt64 db stmtEbTxs 2 (Leios.fromIntegralEbId ebId) + dbExec db (fromString "BEGIN") + forM_ (zip offsets $ V.toList $ txHashes `V.zip` txBytess) $ \(txOffset, (txHash, txBytes)) -> do + -- INTO ebTxs + dbBindInt64 db stmtEbTxs 3 $ fromIntegral txOffset + dbBindBlob db stmtEbTxs 1 $ txBytes + dbStep1 db stmtEbTxs + dbReset db stmtEbTxs + -- INTO txCache + dbBindBlob db stmtTxCache 1 $ (let MkTxHash bytes = txHash in bytes) + dbBindBlob db stmtTxCache 2 $ txBytes + dbBindInt64 db stmtTxCache 3 $ fromIntegral $ BS.length txBytes + dbStep1 db stmtTxCache + dbReset db stmtTxCache + dbExec db (fromString "COMMIT") + -- update NodeKernel state + MVar.modifyMVar_ outstandingVar $ \outstanding -> do + let (requestedTxPeers', cachedTxs', txOffsetss', txsBytesSize) = + (\f -> V.foldl + f + ( + Leios.requestedTxPeers outstanding + , + Leios.cachedTxs outstanding + , + Leios.txOffsetss outstanding + , + 0 + ) + (txHashes `V.zip` txBytess) + ) + $ \(!accReqs, !accCache, !accOffsetss, !accSz) (txHash, txBytes) -> id + $ ( + Map.update (delIf Set.null . Set.delete peerId) txHash accReqs + , + Map.insert txHash (fromIntegral (BS.length txBytes)) accCache + , + Map.update (delIf Map.null . Map.delete ebId) txHash accOffsetss + , + accSz + BS.length txBytes + ) + let !outstanding' = outstanding { + Leios.cachedTxs = cachedTxs' + , + Leios.missingEbTxs = + Map.update + (delIf IntMap.null . flip IntMap.withoutKeys (IntSet.fromList offsets)) + ebId + (Leios.missingEbTxs outstanding) + , + Leios.txOffsetss = txOffsetss' + , + Leios.requestedBytesSize = + Leios.requestedBytesSize outstanding - fromIntegral txsBytesSize + , + Leios.requestedBytesSizePerPeer = + Map.alter + (\case + Nothing -> error "impossible!" + Just x -> delIf (==0) $ x - fromIntegral txsBytesSize + ) + peerId + (Leios.requestedBytesSizePerPeer outstanding) + , + Leios.requestedTxPeers = requestedTxPeers' + } + pure outstanding' + void $ MVar.tryPutMVar readyVar () + +sql_update_ebTx :: String +sql_update_ebTx = + "UPDATE ebTxs\n\ + \SET txBytes = ?\n\ + \WHERE ebId = ? AND txOffset = ? AND txBytes IS NULL\n\ + \" + +sql_insert_txCache :: String +sql_insert_txCache = + "INSERT OR IGNORE INTO txCache (txHashBytes, txBytes, txBytesSize, expiryUnixEpoch) VALUES (?, ?, ?, -1)\n\ + \" + +----- + +doCacheCopy :: + (MonadMVar m, MonadMonotonicTimeNSec m) + => + LeiosDb stmt m -> (MVar m (), MVar m (LeiosOutstanding pid)) -> BytesSize -> m Bool +doCacheCopy db (writeLock, outstandingVar) bytesSize = do + (copied, copiedBytesSize, copiedCount) <- do + outstanding <- MVar.readMVar outstandingVar + (x, t1, t2, t3, t4) <- MVar.withMVar writeLock $ \() -> do + t1 <- getMonotonicTimeNSec + dbExec db (fromString "BEGIN") + stmt <- dbPrepare db (fromString sql_insert_memTxPoints) + -- load in-mem table of ebId-txOffset pairs + x <- go1 stmt Map.empty 0 0 (Leios.toCopy outstanding) + dbFinalize db stmt + t2 <- getMonotonicTimeNSec + -- UPDATE JOIN driven by the loaded table + dbExec db (fromString sql_copy_from_txCache) + t3 <- getMonotonicTimeNSec + dbExec db (fromString sql_flush_memTxPoints) + t4 <- getMonotonicTimeNSec + dbExec db (fromString "COMMIT") + pure (x, t1, t2, t3, t4) + t5 <- getMonotonicTimeNSec + traceM $ "leiosCopySQL1-2: done " ++ show ((t2 - t1) `div` (10^(6 :: Int))) + traceM $ "leiosCopySQL2-3: done " ++ show ((t3 - t2) `div` (10^(6 :: Int))) + traceM $ "leiosCopySQL3-4: done " ++ show ((t4 - t3) `div` (10^(6 :: Int))) + traceM $ "leiosCopySQL4-5: done " ++ show ((t5 - t4) `div` (10^(6 :: Int))) + pure x + (moreTodo, t1) <- MVar.modifyMVar outstandingVar $ \outstanding -> do + t1 <- getMonotonicTimeNSec + let !outstanding' = outstanding { + Leios.toCopy = + MapMerge.merge + MapMerge.preserveMissing + MapMerge.dropMissing -- TODO impossible, so error here? + (MapMerge.zipWithMaybeMatched $ \_ebId toCopy copiedEbId -> + delIf IntMap.null $ toCopy `IntMap.difference` copiedEbId + ) + (Leios.toCopy outstanding) + copied + , + Leios.toCopyBytesSize = Leios.toCopyBytesSize outstanding - copiedBytesSize + , + Leios.toCopyCount = Leios.toCopyCount outstanding - copiedCount + } + pure (outstanding', (0 /= Leios.toCopyCount outstanding', t1)) + t2 <- getMonotonicTimeNSec + traceM $ "leiosCopyUpd: done " ++ show ((t2 - t1) `div` (10^(6 :: Int))) + pure moreTodo + where + go1 stmt !accCopied !accBytesSize !accCount !acc + | accBytesSize < bytesSize + , Just ((ebId, txs), acc') <- Map.maxViewWithKey acc + = go2 stmt accCopied accBytesSize accCount acc' ebId IntMap.empty txs + + | otherwise + = finish accCopied accBytesSize accCount + + go2 stmt !accCopied !accBytesSize !accCount !acc ebId !accCopiedEbId txs + | Just ((txOffset, (txHash, txBytesSize)), txs') <- IntMap.minViewWithKey txs + = if accBytesSize + txBytesSize > bytesSize then stop else do + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + dbBindInt64 db stmt 2 (fromIntegral txOffset) + dbStep1 db stmt + dbReset db stmt + go2 + stmt + accCopied + (accBytesSize + txBytesSize) + (accCount + 1) + acc + ebId + (IntMap.insert txOffset txHash accCopiedEbId) + txs' + | otherwise + = go1 stmt accCopied' accBytesSize accCount acc + where + accCopied' = Map.insertWith IntMap.union ebId accCopiedEbId accCopied + stop = finish accCopied' accBytesSize accCount + + finish accCopied accBytesSize accCount = + pure (accCopied, accBytesSize, accCount) + +sql_copy_from_txCache :: String +sql_copy_from_txCache = + "UPDATE ebTxs\n\ + \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = x.txHashBytes)\n\ + \FROM ebTxs AS x\n\ + \INNER JOIN mem.txPoints ON x.ebId = mem.txPoints.ebId AND x.txOffset = mem.txPoints.txOffset\n\ + \" diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index f481956634..00d5971d1e 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -31,6 +31,7 @@ import Data.String (fromString) import qualified Data.Vector as V import Data.Word (Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB +import qualified Numeric import Ouroboros.Consensus.Util (ShowProxy (..)) import Ouroboros.Consensus.Util.IOLike (IOLike) import System.Directory (doesFileExist) @@ -100,6 +101,15 @@ data LeiosBlockTxsRequest = [(Word16, Word64)] !(V.Vector TxHash) +prettyLeiosBlockTxsRequest :: LeiosBlockTxsRequest -> String +prettyLeiosBlockTxsRequest (MkLeiosBlockTxsRequest p bitmaps _txHashes) = + unwords + $ "MsgLeiosBlockTxs" : prettyLeiosPoint p : map prettyBitmap bitmaps + +prettyBitmap :: (Word16, Word64) -> String +prettyBitmap (idx, bitmap) = + show idx ++ ":0x" ++ Numeric.showHex bitmap "" + ----- -- @@ -173,7 +183,7 @@ data LeiosOutstanding pid = MkLeiosOutstanding { -- TODO this is far too big for the heap txOffsetss :: !(Map TxHash (Map EbId Int)) , - toCopy :: !(Map EbId (IntMap BytesSize)) + toCopy :: !(Map EbId (IntMap (TxHash, BytesSize))) , toCopyBytesSize :: !BytesSize , @@ -194,6 +204,49 @@ emptyLeiosOutstanding = 0 0 +prettyLeiosOutstanding :: LeiosOutstanding pid -> String +prettyLeiosOutstanding x = + unlines $ map (" [leios] " ++) $ + [ + "requestedEbPeers = " ++ unwords (map prettyEbId (Map.keys requestedEbPeers)) + , + "requestedTxPeers = " ++ show (Map.size requestedTxPeers) + , + "requestedBytesSizePerPeer = " ++ show (Map.elems requestedBytesSizePerPeer) + , + "requestedBytesSize = " ++ show requestedBytesSize + , + "missingEbTxs = " ++ unwords [ (prettyEbId k ++ "__" ++ show (IntMap.size v)) | (k, v) <- Map.toList missingEbTxs ] + , + "toCopy = " ++ unwords [ (prettyEbId k ++ "__" ++ show (IntMap.size v)) | (k, v) <- Map.toList toCopy ] + , + "toCopyBytesSize = " ++ show toCopyBytesSize + , + "toCopyCount = " ++ show toCopyCount + , + "" + ] + where + prettyEbId (MkEbId i) = show i + + MkLeiosOutstanding { + requestedEbPeers + , + requestedTxPeers + , + requestedBytesSizePerPeer + , + requestedBytesSize + , + missingEbTxs + , + toCopy + , + toCopyBytesSize + , + toCopyCount + } = x + ----- newtype LeiosTx = MkLeiosTx ByteString @@ -304,7 +357,7 @@ leiosDbFromSqliteDirect db = MkLeiosDb { withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a withDiePoly f io = io >>= \case - Left e -> die $ show $ f e + Left e -> die $ "LeiosDb: " ++ show (f e) Right x -> pure x withDieMsg :: IO (Either (DB.Error, DB.Utf8) a) -> IO a @@ -316,13 +369,13 @@ withDie = withDiePoly id withDieJust :: IO (Either DB.Error (Maybe a)) -> IO a withDieJust io = withDie io >>= \case - Nothing -> die "impossible!" + Nothing -> die $ "LeiosDb: [Just] " ++ "impossible!" Just x -> pure x withDieDone :: IO (Either DB.Error DB.StepResult) -> IO () withDieDone io = withDie io >>= \case - DB.Row -> die "impossible!" + DB.Row -> die $ "LeiosDb: [Done] " ++ "impossible!" DB.Done -> pure () ----- From c1a2c958777bb07232e7ceeb083d39f023590067 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Sun, 26 Oct 2025 22:39:53 -0700 Subject: [PATCH 094/119] WIP bugfix, see longer message This commit fixes two bugs: 1) The JOIN-based UPDATE for copying from txCache to ebTxs was taking ~72 seconds. I replaced it with just a single-row UPDATE per index, and that seems better. I'm surprised, but maybe the bulk update query SQL can be tuned another time. 2) `packRequests` had a bug where it'd fail to request one tx whenever it had to flush due to size. Instead of being the first tx in the next request, it was simply never requested. It also leaves all the debug stuff in, because I need to go to bed. --- .../Ouroboros/Consensus/NodeKernel.hs | 8 ++++ .../src/ouroboros-consensus/LeiosDemoLogic.hs | 42 ++++++------------- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 29 +++++++++++-- 3 files changed, 45 insertions(+), 34 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 4e03d2afc9..fb45443ed4 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -132,6 +132,7 @@ import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar import Data.Map (Map) import qualified Data.Map as Map +import qualified Data.Set as Set import LeiosDemoTypes (LeiosEbBodies, LeiosOutstanding, LeiosPeerVars, SomeLeiosDb) import qualified LeiosDemoTypes as Leios @@ -399,8 +400,15 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers pure (outstanding', (newDecisions, newCopy, outstanding, outstanding')) let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" ++ "\n" ++ + "leiosOfferings: " ++ unwords [ Leios.prettyEbId ebId | (_peer, (_offers1, offers2)) <- Map.toList offerings, ebId <- Set.toList offers2 ] ++ "\n" ++ + "leiosEbBodies: " ++ Leios.prettyLeiosEbBodies ebBodies ++ "\n" ++ "leiosOutstanding: " ++ Leios.prettyLeiosOutstanding xxx ++ "\n" ++ "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" + forM_ newRequests $ \perPeer -> forM_ perPeer $ \case + Leios.LeiosBlockRequest _ -> pure () + Leios.LeiosBlockTxsRequest (Leios.MkLeiosBlockTxsRequest _p _bitmaps txHashes) -> do + forM_ txHashes $ \txHash -> do + traceM $ "leiosReqTxHash: " ++ Leios.prettyTxHash txHash (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> atomically $ do StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index f98c6da9e7..ccdc1f7287 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -16,7 +16,6 @@ import Control.Concurrent.Class.MonadSTM (MonadSTM) import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import Control.Monad (foldM, when) -import Control.Monad.Class.MonadTime (MonadMonotonicTimeNSec, getMonotonicTimeNSec) import Control.Monad.Primitive (PrimMonad, PrimState) import qualified Data.Bits as Bits import Data.ByteString (ByteString) @@ -573,10 +572,10 @@ packRequests env ebBodies = -- be simplified away goEb p !accTxBytesSize !accBitmaps !accN !accHashes = \case [] -> if 0 < accN then Seq.singleton flush else Seq.empty - (txOffset, (txHash, txBytesSize)):txs + txsAgain@((txOffset, (txHash, txBytesSize)):txs) | Leios.maxRequestBytesSize env < accTxBytesSize' - -> flush Seq.:<| goEb p 0 IntMap.empty 0 DList.empty txs + -> flush Seq.:<| goEb p 0 IntMap.empty 0 DList.empty txsAgain | otherwise , let (q, r) = txOffset `divMod` 64 @@ -794,6 +793,8 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re traceM $ Leios.prettyLeiosBlockTxsRequest req -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req + forM_ txHashes $ \txHash -> do + traceM $ "leiosRspTxHash: " ++ Leios.prettyTxHash txHash let txBytess :: V.Vector ByteString txBytess = V.map (serialize' . Leios.encodeLeiosTx) txs do @@ -909,35 +910,20 @@ sql_insert_txCache = ----- doCacheCopy :: - (MonadMVar m, MonadMonotonicTimeNSec m) + MonadMVar m => LeiosDb stmt m -> (MVar m (), MVar m (LeiosOutstanding pid)) -> BytesSize -> m Bool doCacheCopy db (writeLock, outstandingVar) bytesSize = do (copied, copiedBytesSize, copiedCount) <- do outstanding <- MVar.readMVar outstandingVar - (x, t1, t2, t3, t4) <- MVar.withMVar writeLock $ \() -> do - t1 <- getMonotonicTimeNSec + MVar.withMVar writeLock $ \() -> do dbExec db (fromString "BEGIN") - stmt <- dbPrepare db (fromString sql_insert_memTxPoints) - -- load in-mem table of ebId-txOffset pairs + stmt <- dbPrepare db (fromString sql_copy_from_txCache) x <- go1 stmt Map.empty 0 0 (Leios.toCopy outstanding) dbFinalize db stmt - t2 <- getMonotonicTimeNSec - -- UPDATE JOIN driven by the loaded table - dbExec db (fromString sql_copy_from_txCache) - t3 <- getMonotonicTimeNSec - dbExec db (fromString sql_flush_memTxPoints) - t4 <- getMonotonicTimeNSec dbExec db (fromString "COMMIT") - pure (x, t1, t2, t3, t4) - t5 <- getMonotonicTimeNSec - traceM $ "leiosCopySQL1-2: done " ++ show ((t2 - t1) `div` (10^(6 :: Int))) - traceM $ "leiosCopySQL2-3: done " ++ show ((t3 - t2) `div` (10^(6 :: Int))) - traceM $ "leiosCopySQL3-4: done " ++ show ((t4 - t3) `div` (10^(6 :: Int))) - traceM $ "leiosCopySQL4-5: done " ++ show ((t5 - t4) `div` (10^(6 :: Int))) - pure x - (moreTodo, t1) <- MVar.modifyMVar outstandingVar $ \outstanding -> do - t1 <- getMonotonicTimeNSec + pure x + MVar.modifyMVar outstandingVar $ \outstanding -> do let !outstanding' = outstanding { Leios.toCopy = MapMerge.merge @@ -953,10 +939,7 @@ doCacheCopy db (writeLock, outstandingVar) bytesSize = do , Leios.toCopyCount = Leios.toCopyCount outstanding - copiedCount } - pure (outstanding', (0 /= Leios.toCopyCount outstanding', t1)) - t2 <- getMonotonicTimeNSec - traceM $ "leiosCopyUpd: done " ++ show ((t2 - t1) `div` (10^(6 :: Int))) - pure moreTodo + pure (outstanding', 0 /= Leios.toCopyCount outstanding') where go1 stmt !accCopied !accBytesSize !accCount !acc | accBytesSize < bytesSize @@ -994,7 +977,6 @@ doCacheCopy db (writeLock, outstandingVar) bytesSize = do sql_copy_from_txCache :: String sql_copy_from_txCache = "UPDATE ebTxs\n\ - \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = x.txHashBytes)\n\ - \FROM ebTxs AS x\n\ - \INNER JOIN mem.txPoints ON x.ebId = mem.txPoints.ebId AND x.txOffset = mem.txPoints.txOffset\n\ + \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = ebTxs.txHashBytes)\n\ + \WHERE ebId = ? AND txOffset = ?\n\ \" diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 00d5971d1e..557f515e2c 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -43,6 +43,9 @@ type BytesSize = Word32 newtype EbId = MkEbId Int deriving (Eq, Ord) +prettyEbId :: EbId -> String +prettyEbId (MkEbId i) = show i + fromIntegralEbId :: Integral a => EbId -> a fromIntegralEbId (MkEbId x) = fromIntegral x @@ -55,6 +58,9 @@ newtype EbHash = MkEbHash ByteString newtype TxHash = MkTxHash ByteString deriving (Eq, Ord, Show) +prettyTxHash :: TxHash -> String +prettyTxHash (MkTxHash bytes) = BS8.unpack (BS16.encode bytes) + data LeiosPoint = MkLeiosPoint SlotNo EbHash deriving (Show) @@ -96,7 +102,7 @@ data LeiosBlockTxsRequest = -- -- The hashes aren't sent to the peer, but they are used to validate the -- response when it arrives. - MkLeiosBlockTxsRequest + MkLeiosBlockTxsRequest !LeiosPoint [(Word16, Word64)] !(V.Vector TxHash) @@ -165,6 +171,23 @@ emptyLeiosEbBodies = IntMap.empty IntMap.empty +prettyLeiosEbBodies :: LeiosEbBodies -> String +prettyLeiosEbBodies x = + unwords + [ + "LeiosEbBodies:" + , + "acquiredEbBodies = " ++ show (Set.size acquiredEbBodies) + , + "missingEbBodies = " ++ show (Map.size missingEbBodies) + ] + where + MkLeiosEbBodies { + acquiredEbBodies + , + missingEbBodies + } = x + data LeiosOutstanding pid = MkLeiosOutstanding { requestedEbPeers :: !(Map EbId (Set (PeerId pid))) , @@ -210,7 +233,7 @@ prettyLeiosOutstanding x = [ "requestedEbPeers = " ++ unwords (map prettyEbId (Map.keys requestedEbPeers)) , - "requestedTxPeers = " ++ show (Map.size requestedTxPeers) + "requestedTxPeers = " ++ unwords (map prettyTxHash (Map.keys requestedTxPeers)) , "requestedBytesSizePerPeer = " ++ show (Map.elems requestedBytesSizePerPeer) , @@ -227,8 +250,6 @@ prettyLeiosOutstanding x = "" ] where - prettyEbId (MkEbId i) = show i - MkLeiosOutstanding { requestedEbPeers , From 473d06fd7bae208cc5eb9578d442d8c8fdc31b1d Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 07:51:26 -0700 Subject: [PATCH 095/119] WIP disable the most noisy traces --- .../Ouroboros/Consensus/NodeKernel.hs | 6 ++++-- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 4 ++-- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index fb45443ed4..971bb24368 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -399,16 +399,18 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers let newCopy = Leios.toCopyCount outstanding' /= Leios.toCopyCount outstanding pure (outstanding', (newDecisions, newCopy, outstanding, outstanding')) let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions - traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" ++ "\n" ++ + traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" {- ++ "\n" ++ "leiosOfferings: " ++ unwords [ Leios.prettyEbId ebId | (_peer, (_offers1, offers2)) <- Map.toList offerings, ebId <- Set.toList offers2 ] ++ "\n" ++ "leiosEbBodies: " ++ Leios.prettyLeiosEbBodies ebBodies ++ "\n" ++ "leiosOutstanding: " ++ Leios.prettyLeiosOutstanding xxx ++ "\n" ++ - "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" + "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" -} +{- forM_ newRequests $ \perPeer -> forM_ perPeer $ \case Leios.LeiosBlockRequest _ -> pure () Leios.LeiosBlockTxsRequest (Leios.MkLeiosBlockTxsRequest _p _bitmaps txHashes) -> do forM_ txHashes $ \txHash -> do traceM $ "leiosReqTxHash: " ++ Leios.prettyTxHash txHash +-} (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> atomically $ do StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index ccdc1f7287..92397a025d 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -793,8 +793,8 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re traceM $ Leios.prettyLeiosBlockTxsRequest req -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req - forM_ txHashes $ \txHash -> do - traceM $ "leiosRspTxHash: " ++ Leios.prettyTxHash txHash +-- forM_ txHashes $ \txHash -> do +-- traceM $ "leiosRspTxHash: " ++ Leios.prettyTxHash txHash let txBytess :: V.Vector ByteString txBytess = V.map (serialize' . Leios.encodeLeiosTx) txs do From 6438535819cf22014af1222b0989fa47903e6f40 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 08:37:45 -0700 Subject: [PATCH 096/119] WIP fixup warnings --- .../Ouroboros/Consensus/NodeKernel.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 971bb24368..1cdc520b8f 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -132,7 +132,7 @@ import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar import Data.Map (Map) import qualified Data.Map as Map -import qualified Data.Set as Set +-- import qualified Data.Set as Set import LeiosDemoTypes (LeiosEbBodies, LeiosOutstanding, LeiosPeerVars, SomeLeiosDb) import qualified LeiosDemoTypes as Leios @@ -390,7 +390,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers leiosPeersVars <- MVar.readMVar getLeiosPeersVars offerings <- mapM (MVar.readMVar . Leios.offerings) leiosPeersVars ebBodies <- MVar.readMVar getLeiosEbBodies - (newDecisions, newCopy, xxx, yyy) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do + (newDecisions, newCopy, _xxx, _yyy) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do let (!outstanding', newDecisions) = Leios.leiosFetchLogicIteration Leios.demoLeiosFetchStaticEnv From 772f6eeadc4a42545ee4fa66a48bcb4f23a9a888 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 09:32:43 -0700 Subject: [PATCH 097/119] leiosdemo202510: drop the netstat stuff This originated when I was debugging busy ports. Turns out I had some docker containers running that I wasn't aware of (and they kept restarting). Once I eventually noticed and dropped those containers, there were no more unexpectedly-busy ports. --- scripts/leios-demo/leios-october-demo.sh | 30 ++++-------------------- 1 file changed, 4 insertions(+), 26 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 34881a2baa..cbd8c95479 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -2,11 +2,6 @@ now=$(date +%s) -if [[ -z "${NETSTAT_OUTPUT}" ]]; then - echo "Error: \${NETSTAT_OUTPUT} must be the path to the stdout of a recent call to netstat -lntp." >&2 - exit 1 -fi - if [[ ! "$SECONDS_UNTIL_REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$SECONDS_UNTIL_REF_SLOT" -le 0 ]]; then echo "Error: \${SECONDS_UNTIL_REF_SLOT} must be a positive integer of seconds, which will be added to the execution time of this script." >&2 exit 1 @@ -43,28 +38,11 @@ if [[ -z "${REF_SLOT}" ]] || [[ ! "$REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$REF_SLOT" - exit 1 fi -find_random_unused_port() { - local port - local min_port=1024 # Start checking from non-privileged ports - local max_port=65535 # Maximum possible port number - - while true; do - # Generate a random port within the specified range - port=$(( RANDOM % (max_port - min_port + 1) + min_port )) - - # Check if the port is in use using netstat - # -l: listening sockets, -t: TCP, -n: numeric addresses, -p: show PID/program name - # grep -q: quiet mode, exits with 0 if match found, 1 otherwise - if ! cat ${NETSTAT_OUTPUT} | grep -q ":$port "; then - echo "$port" - return 0 # Port found, exit function - fi - done -} +# arbitrary choices -PORT1=$(find_random_unused_port) -PORT2=$(find_random_unused_port) -PORT3=$(find_random_unused_port) +PORT1=3001 +PORT2=3002 +PORT3=3003 echo "Ports: ${PORT1} ${PORT2} ${PORT3}" From e7aed1e190dc29ccec58b6c1dcd2bb2843bfd563 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 09:39:24 -0700 Subject: [PATCH 098/119] leiosdemo202510: consolidate magic numbers (absorbing maxIngressQueue) --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 13 +++++++++++-- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 10 ++++++++++ 2 files changed, 21 insertions(+), 2 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index b745e04d4b..a6bb1dc09f 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -1167,13 +1167,22 @@ initiatorAndResponder miniProtocolParameters version versionData Apps {..} = leiosNotifyProtocolLimits :: MiniProtocolLimits leiosNotifyProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 1 * 2 ^ (20 :: Int) -- 1 mebibyte + ON.maximumIngressQueue = + addSafetyMargin + $ fromIntegral + $ Leios.maxLeiosNotifyIngressQueue + $ Leios.demoLeiosFetchStaticEnv } leiosFetchProtocolLimits :: MiniProtocolLimits leiosFetchProtocolLimits = ON.MiniProtocolLimits { - ON.maximumIngressQueue = addSafetyMargin $ 50 * 2 ^ (20 :: Int) -- 50 mebibytes + ON.maximumIngressQueue = + addSafetyMargin + $ fromIntegral + $ Leios.maxLeiosFetchIngressQueue + $ Leios.demoLeiosFetchStaticEnv } +-- | Copied from ouroboros-network addSafetyMargin :: Int -> Int addSafetyMargin x = x + x `div` 10 diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 557f515e2c..c6fdd909e1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -456,6 +456,12 @@ data LeiosFetchStaticEnv = MkLeiosFetchStaticEnv { , -- | At most this many txs are scheduled to be copied from the TxCache to the EbStore maxToCopyCount :: Int + , + -- | @maximumIngressQueue@ for LeiosNotify + maxLeiosNotifyIngressQueue :: BytesSize + , + -- | @maximumIngressQueue@ for LeiosFetch + maxLeiosFetchIngressQueue :: BytesSize } demoLeiosFetchStaticEnv :: LeiosFetchStaticEnv @@ -474,6 +480,10 @@ demoLeiosFetchStaticEnv = maxToCopyBytesSize = 100 * millionBase2 , maxToCopyCount = 100 * thousand + , + maxLeiosNotifyIngressQueue = 1 * millionBase2 + , + maxLeiosFetchIngressQueue = 50 * millionBase2 } where million :: Num a => a From fe3b41fb940e16100605b48188941cffcdba82f7 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 09:45:19 -0700 Subject: [PATCH 099/119] leiosdemo202510: consolidate ebId magic number --- ouroboros-consensus/app/leiosdemo202510.hs | 14 +++++++++----- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 9 ++++++--- 2 files changed, 15 insertions(+), 8 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index 0c3dd29ff1..f5edb88f33 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -1019,9 +1019,13 @@ emptyLeiosFetchState = 0 0 +-- | See 'ebPoints' +ebIdBitWidthOfSlot :: Int +ebIdBitWidthOfSlot = 20 + ebIdSlot :: EbId -> Word64 ebIdSlot (MkEbId y) = - fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64 + fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` ebIdBitWidthOfSlot :: Word64 ebIdToPoint :: EbId -> LeiosFetchDynamicEnv -> Maybe (Word64, ByteString) ebIdToPoint (MkEbId y) x = @@ -1034,12 +1038,12 @@ ebIdFromPoint ebSlot ebHash x = case IntMap.lookup (fromIntegral ebSlot) (ebPoints x) of Just m -> case Map.lookup hashBytes m of Just y -> (y, Nothing) - Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) - Map.size m - Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) + Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) - Map.size m + Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) where hashBytes = MkHashBytes ebHash - zero = fromIntegral ((ebSlot `Bits.unsafeShiftL` 20) :: Word64) + minBound :: Int + zero = fromIntegral ((ebSlot `Bits.unsafeShiftL` ebIdBitWidthOfSlot) :: Word64) + minBound :: Int gen y = (,) y @@ -1641,7 +1645,7 @@ doCacheCopy db lfst bytesSize = do lfst' <- go1 stmt 0 0 (toCopy lfst) withDie $ DB.finalize stmt -- UPDATE JOIN driven by the loaded table - withDieMsg $ DB.exec db (fromString sql_copy_from_txCache) + withDieMsg $ DB.exec db (fromString sql_copy_from_txCache) -- TODO this was tragically slow in the node withDieMsg $ DB.exec db (fromString "COMMIT") withDieMsg $ DB.exec db (fromString sql_detach_memTxPoints) pure lfst' diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 92397a025d..17fa4563a7 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -52,6 +52,9 @@ ebIdSlot :: EbId -> SlotNo ebIdSlot (MkEbId y) = SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) +ebIdBitWidthOfSlot :: Int +ebIdBitWidthOfSlot = 20 + ebIdToPoint :: EbId -> LeiosEbBodies -> Maybe LeiosPoint ebIdToPoint (MkEbId i) x = (\h -> MkLeiosPoint (ebIdSlot (MkEbId i)) h) @@ -67,14 +70,14 @@ ebIdFromPoint p x = case IntMap.lookup islot (Leios.ebPoints x) of Just m -> case Map.lookup ebHash m of Just y -> (y, Nothing) - Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) - Map.size m - Nothing -> gen $ MkEbId $ zero + (2^(20 :: Int) - 1) + Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) - Map.size m + Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) where MkLeiosPoint ebSlot ebHash = p SlotNo wslot = ebSlot islot = fromIntegral (wslot :: Word64) - zero = fromIntegral (wslot `Bits.unsafeShiftL` 20) + minBound :: Int + zero = fromIntegral (wslot `Bits.unsafeShiftL` ebIdBitWidthOfSlot) + minBound :: Int gen y = let !x' = x { From c567c18fb9e1a13061feadd908dded4975838898 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 10:13:16 -0700 Subject: [PATCH 100/119] leiosdemo202510: also generate typical schedule.json file --- ouroboros-consensus/app/leiosdemo202510.hs | 56 +++++++++++++++++----- 1 file changed, 44 insertions(+), 12 deletions(-) diff --git a/ouroboros-consensus/app/leiosdemo202510.hs b/ouroboros-consensus/app/leiosdemo202510.hs index f5edb88f33..0c924f3170 100644 --- a/ouroboros-consensus/app/leiosdemo202510.hs +++ b/ouroboros-consensus/app/leiosdemo202510.hs @@ -31,7 +31,7 @@ import qualified Data.Foldable as Foldable import Data.Functor.Contravariant ((>$<)) import qualified Data.IntMap as IntMap import Data.IntMap (IntMap) -import Data.List (isSuffixOf, unfoldr) +import Data.List (intercalate, isSuffixOf, unfoldr) import Data.Map (Map) import Data.Maybe (fromMaybe) import qualified Data.Map.Strict as Map @@ -58,9 +58,10 @@ main = flip asTypeOf main2 $ do main2 :: IO () main2 = getArgs >>= \case - ["generate", dbPath, manifestPath] + ["generate", dbPath, manifestPath, schedulePath] | ".db" `isSuffixOf` dbPath , ".json" `isSuffixOf` manifestPath + , ".json" `isSuffixOf` schedulePath -> do doesFileExist dbPath >>= \case True -> die "database path must not exist" @@ -68,9 +69,18 @@ main2 = getArgs >>= \case manifest <- fmap JSON.eitherDecode (BSL.readFile manifestPath) >>= \case Left err -> die err Right x -> pure x + doesFileExist schedulePath >>= \case + True -> die "schedule path must not exist" + False -> pure () db <- withDieMsg $ DB.open (fromString dbPath) prng0 <- R.initStdGen - generateDb prng0 db manifest + schedule <- generateDb prng0 db manifest + writeFile schedulePath + $ (\s -> "[\n " ++ s ++ "\n]\n") + $ intercalate "\n,\n " + $ [ BS8.unpack $ BSL.toStrict $ JSON.encode item + | item <- schedule + ] "ebId-to-point" : dbPath : ebIdStrs | ".db" `isSuffixOf` dbPath , not (null ebIdStrs) @@ -164,7 +174,7 @@ main2 = getArgs >>= \case acc' <- doCacheCopy db acc bytesSize JSON.encodeFile lfstPath acc' _ -> - die "Either $0 generate my.db myManifest.json\n\ + die "Either $0 generate my.db myManifest.json outputSchedule.json\n\ \ OR $0 ebId-to-point my.db ebId ebId ebId...\n\ \ OR $0 MsgLeiosBlockOffer my.db my.lfst peerId ebSlot ebHash(hex) ebBytesSize\n\ \ OR $0 MsgLeiosBlockRequest my.db ebSlot ebHash(hex)\n\ @@ -244,7 +254,13 @@ instance JSON.FromJSON EbRecipeElem where type HASH = Hash.Blake2b_256 -generateDb :: R.RandomGen g => g -> DB.Database -> [EbRecipe] -> IO () +newtype LeiosScheduleItem = MkLeiosScheduleItem (Double, (Word64, T.Text, Maybe Word32)) + deriving (Generic) + +-- | Deriving via "GHC.Generics" +instance JSON.ToJSON LeiosScheduleItem + +generateDb :: R.RandomGen g => g -> DB.Database -> [EbRecipe] -> IO [LeiosScheduleItem] generateDb prng0 db ebRecipes = do gref <- R.newIOGenM prng0 -- init db @@ -252,7 +268,7 @@ generateDb prng0 db ebRecipes = do stmt_write_ebId <- withDieJust $ DB.prepare db (fromString sql_insert_ebId) stmt_write_ebClosure <- withDieJust $ DB.prepare db (fromString sql_insert_ebClosure) -- loop over EBs (one SQL transaction each, to be gentle) - (_dynEnv', sigma) <- (\f -> foldM f (emptyLeiosFetchDynEnv, Map.empty) ebRecipes) $ \(dynEnv, sigma) ebRecipe -> do + (_dynEnv', sigma, revSchedule) <- (\f -> foldM f (emptyLeiosFetchDynEnv, Map.empty, []) ebRecipes) $ \(dynEnv, sigma, revSchedule) ebRecipe -> do -- generate txs, so we have their hashes let finishX (n, x) = V.fromListN n $ Foldable.toList $ revX x -- TODO in ST with mut vector txs <- fmap finishX $ (\f -> V.foldM f (0, emptyX) (ebRecipeElems ebRecipe)) $ \(accN, accX) -> \case @@ -302,12 +318,16 @@ generateDb prng0 db ebRecipes = do let txHash = Hash.hashWith id txBytes :: Hash.Hash HASH ByteString pure (accN + 1, accX `pushX` (txBytes, MkHashBytes $ Hash.hashToBytes txHash)) let ebSlot = ebRecipeSlotNo ebRecipe - let ebHash :: Hash.Hash HASH ByteString - ebHash = - Hash.castHash - $ Hash.hashWithSerialiser - (encodeEB (V.length txs) (fromIntegral . BS.length) (\(MkHashBytes x) -> x)) + let ebBytes :: ByteString + ebBytes = + serialize' + $ encodeEB + (V.length txs) + (fromIntegral . BS.length) + (\(MkHashBytes x) -> x) txs + ebHash :: Hash.Hash HASH ByteString + ebHash = Hash.castHash $ Hash.hashWith id ebBytes let (ebId, mbDynEnv') = ebIdFromPoint ebSlot (Hash.hashToBytes ebHash) dynEnv withDieMsg $ DB.exec db (fromString "BEGIN") withDie $ DB.bindInt64 stmt_write_ebId 3 (fromIntegralEbId ebId) @@ -328,11 +348,23 @@ generateDb prng0 db ebRecipes = do withDie $ DB.reset stmt_write_ebClosure -- finalize each EB withDieMsg $ DB.exec db (fromString "COMMIT") - pure (fromMaybe dynEnv mbDynEnv', maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeNickname ebRecipe) sigma) + pure ( + fromMaybe dynEnv mbDynEnv' + , + maybe id (\bndr -> Map.insert bndr (ebId, V.length txs)) (ebRecipeNickname ebRecipe) sigma + , + let txt = T.pack $ BS8.unpack $ BS16.encode $ Hash.hashToBytes ebHash + in + -- NB reversed! + MkLeiosScheduleItem (fromIntegral ebSlot + 0.2, (ebSlot, txt, Nothing)) + : MkLeiosScheduleItem (fromIntegral ebSlot + 0.1, (ebSlot, txt, Just $ fromIntegral $ BS.length ebBytes)) + : revSchedule + ) -- finalize db withDieMsg $ DB.exec db (fromString sql_index_schema) forM_ (Map.toList sigma) $ \(nickname, (ebId, _count)) -> do putStrLn $ unwords [nickname, prettyEbId ebId] + pure $ reverse revSchedule ----- From 15c2a46556332ee8626fd54f51ff7a470a25394b Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 15:36:51 -0700 Subject: [PATCH 101/119] leiosdemo202510: track outstanding EbTxs count per EB --- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 120 ++++++++++++++---- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 43 ++++++- scripts/leios-demo/leios-october-demo.sh | 3 + 3 files changed, 137 insertions(+), 29 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 17fa4563a7..7158ae3bde 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -26,11 +26,11 @@ import Data.Foldable (forM_) import Data.Functor ((<&>), void) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap +import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet import Data.List (unfoldr) import Data.Map (Map) import qualified Data.Map as Map -import qualified Data.Map.Merge.Strict as MapMerge import Data.Sequence (Seq) import qualified Data.Sequence as Seq import Data.Set (Set) @@ -398,7 +398,7 @@ leiosFetchLogicIteration env (ebBodies, offerings) = Map.insertWith IntMap.union ebId - (IntMap.singleton txOffset (txHash, txBytesSize)) + (IntMap.singleton txOffset txBytesSize) (Leios.toCopy acc) , Leios.toCopyBytesSize = Leios.toCopyBytesSize acc + txBytesSize @@ -725,6 +725,13 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req e pure (ebBodies', (ebId, novel)) MVar.modifyMVar_ outstandingVar $ \outstanding -> do let !outstanding' = outstanding { + Leios.blockingPerEb = + if not novel then Leios.blockingPerEb outstanding else + Map.insert + ebId + (let MkLeiosEb v = eb in V.length v) + (Leios.blockingPerEb outstanding) + , Leios.missingEbTxs = if not novel then Leios.missingEbTxs outstanding else Map.insert @@ -870,16 +877,43 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re , accSz + BS.length txBytes ) + let offsetsSet = IntSet.fromList offsets + beatOtherPeers = + -- the requests that this MsgLeiosBlockTxs was the first to + -- resolve + (`IntMap.restrictKeys` IntSet.fromList offsets) + $ Map.findWithDefault + IntMap.empty + ebId + (Leios.toCopy outstanding) + beatToCopy = + -- the currently scheduled 'toCopy' operations that this + -- MsgLeiosBlockTxs just won the race against + (`IntMap.restrictKeys` IntSet.fromList offsets) + $ Map.findWithDefault + IntMap.empty + ebId + (Leios.toCopy outstanding) let !outstanding' = outstanding { Leios.cachedTxs = cachedTxs' , Leios.missingEbTxs = Map.update - (delIf IntMap.null . flip IntMap.withoutKeys (IntSet.fromList offsets)) + (delIf IntMap.null . (`IntMap.withoutKeys` offsetsSet)) ebId (Leios.missingEbTxs outstanding) , Leios.txOffsetss = txOffsetss' + , + Leios.blockingPerEb = + if IntMap.null beatOtherPeers then Leios.blockingPerEb outstanding else + Map.alter + (\case + Nothing -> Nothing + Just x -> delIf (==0) $ x - IntMap.size beatOtherPeers + ) + ebId + (Leios.blockingPerEb outstanding) , Leios.requestedBytesSize = Leios.requestedBytesSize outstanding - fromIntegral txsBytesSize @@ -894,6 +928,24 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re (Leios.requestedBytesSizePerPeer outstanding) , Leios.requestedTxPeers = requestedTxPeers' + , + Leios.toCopy = + if IntMap.null beatToCopy then Leios.toCopy outstanding else + Map.alter + (\case + Nothing -> Nothing + Just x -> + delIf IntMap.null + $ x `IntMap.difference` beatToCopy + ) + ebId + (Leios.toCopy outstanding) + , + Leios.toCopyBytesSize = + Leios.toCopyBytesSize outstanding - sum beatToCopy + , + Leios.toCopyCount = + Leios.toCopyCount outstanding - IntMap.size beatToCopy } pure outstanding' void $ MVar.tryPutMVar readyVar () @@ -917,44 +969,61 @@ doCacheCopy :: => LeiosDb stmt m -> (MVar m (), MVar m (LeiosOutstanding pid)) -> BytesSize -> m Bool doCacheCopy db (writeLock, outstandingVar) bytesSize = do - (copied, copiedBytesSize, copiedCount) <- do + copied <- do outstanding <- MVar.readMVar outstandingVar MVar.withMVar writeLock $ \() -> do dbExec db (fromString "BEGIN") stmt <- dbPrepare db (fromString sql_copy_from_txCache) - x <- go1 stmt Map.empty 0 0 (Leios.toCopy outstanding) + x <- go1 stmt Map.empty 0 (Leios.toCopy outstanding) dbFinalize db stmt dbExec db (fromString "COMMIT") pure x MVar.modifyMVar outstandingVar $ \outstanding -> do + let _ = copied :: Map EbId IntSet + let usefulCopied = + -- @copied@ might contain elements that were already accounted + -- for by a @MsgLeiosBlockTxs@ that won the race. This + -- intersection discards those. + Map.intersectionWith + IntMap.restrictKeys + (Leios.toCopy outstanding) + copied let !outstanding' = outstanding { + Leios.blockingPerEb = + Map.differenceWithKey + (\_ebId count copiedEbId -> + delIf (==0) $ count - IntMap.size copiedEbId + ) + (Leios.blockingPerEb outstanding) + usefulCopied + , Leios.toCopy = - MapMerge.merge - MapMerge.preserveMissing - MapMerge.dropMissing -- TODO impossible, so error here? - (MapMerge.zipWithMaybeMatched $ \_ebId toCopy copiedEbId -> - delIf IntMap.null $ toCopy `IntMap.difference` copiedEbId + Map.differenceWithKey + (\_ebId toCopy copiedEbId -> + delIf IntMap.null $ toCopy `IntMap.difference` copiedEbId ) (Leios.toCopy outstanding) - copied + usefulCopied , - Leios.toCopyBytesSize = Leios.toCopyBytesSize outstanding - copiedBytesSize + Leios.toCopyBytesSize = + Leios.toCopyBytesSize outstanding - sum (Map.map sum usefulCopied) , - Leios.toCopyCount = Leios.toCopyCount outstanding - copiedCount + Leios.toCopyCount = + Leios.toCopyCount outstanding - sum (Map.map IntMap.size usefulCopied) } pure (outstanding', 0 /= Leios.toCopyCount outstanding') where - go1 stmt !accCopied !accBytesSize !accCount !acc + go1 stmt !accCopied !accBytesSize !acc | accBytesSize < bytesSize , Just ((ebId, txs), acc') <- Map.maxViewWithKey acc - = go2 stmt accCopied accBytesSize accCount acc' ebId IntMap.empty txs + = go2 stmt accCopied accBytesSize acc' ebId IntSet.empty txs | otherwise - = finish accCopied accBytesSize accCount + = pure accCopied - go2 stmt !accCopied !accBytesSize !accCount !acc ebId !accCopiedEbId txs - | Just ((txOffset, (txHash, txBytesSize)), txs') <- IntMap.minViewWithKey txs - = if accBytesSize + txBytesSize > bytesSize then stop else do + go2 stmt !accCopied !accBytesSize !acc ebId !accCopiedEbId txs + | Just ((txOffset, txBytesSize), txs') <- IntMap.minViewWithKey txs + = if accBytesSize + txBytesSize > bytesSize then pure accCopied' else do dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) dbBindInt64 db stmt 2 (fromIntegral txOffset) dbStep1 db stmt @@ -963,23 +1032,18 @@ doCacheCopy db (writeLock, outstandingVar) bytesSize = do stmt accCopied (accBytesSize + txBytesSize) - (accCount + 1) acc ebId - (IntMap.insert txOffset txHash accCopiedEbId) + (IntSet.insert txOffset accCopiedEbId) txs' | otherwise - = go1 stmt accCopied' accBytesSize accCount acc + = go1 stmt accCopied' accBytesSize acc where - accCopied' = Map.insertWith IntMap.union ebId accCopiedEbId accCopied - stop = finish accCopied' accBytesSize accCount - - finish accCopied accBytesSize accCount = - pure (accCopied, accBytesSize, accCount) + accCopied' = Map.insertWith IntSet.union ebId accCopiedEbId accCopied sql_copy_from_txCache :: String sql_copy_from_txCache = "UPDATE ebTxs\n\ \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = ebTxs.txHashBytes)\n\ - \WHERE ebId = ? AND txOffset = ?\n\ + \WHERE ebId = ? AND txOffset = ? AND txBytes IS NULL\n\ \" diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index c6fdd909e1..77ac46a23a 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -200,13 +200,49 @@ data LeiosOutstanding pid = MkLeiosOutstanding { -- TODO this might be far too big for the heap cachedTxs :: !(Map TxHash BytesSize) , + -- | The txs that still need to be sourced + -- + -- * A @MsgLeiosBlock@ inserts into 'missingEbTxs' if that EB has never + -- been received before. + -- + -- * Every @MsgLeiosBlockTxs@ deletes from 'missingEbTxs', but that delete + -- will be a no-op for all except the first to arrive carrying this EbTx. + -- + -- * EbTxs are deleted from 'missingEbTxs' when a 'toCopy' is scheduled + -- (b/c we can immediately stop requesting it from any peer). This delete + -- will never be a no-op (except maybe in a race?). + -- -- TODO this is far too big for the heap missingEbTxs :: !(Map EbId (IntMap (TxHash, BytesSize))) , -- TODO this is far too big for the heap + -- + -- inverse of missingEbTxs txOffsetss :: !(Map TxHash (Map EbId Int)) , - toCopy :: !(Map EbId (IntMap (TxHash, BytesSize))) + -- | How many txs of each EB are not yet in the @ebTxs@ table + -- + -- These NULLs are blocking the node from sending @MsgLeiosBlockTxsOffer@ + -- to its downstream peers. + -- + -- It's different from 'missingEbTxs' in two ways. + -- + -- * The heap footprint of 'blockingPerEb' doesn't scale with the number of + -- EbTxs. + -- + -- * 'blockingPerEb' is only updated when a 'toCopy' /finishes/ instead of as + -- soon as it's /scheduled/. + -- + -- We need to be careful not to double-count arrivals. 'blockingPerEb' + -- should only be decremented by the arrival of a @MsgLeiosBlockTx@ if + -- + -- * The EbTx is in 'missingEbTxs'. + -- + -- * The EbTx is in 'toCopy' (and therefore not in 'missingEbTxs'). The + -- handler shoulder also remove it from 'toCopy'. + blockingPerEb :: !(Map EbId Int) + , + toCopy :: !(Map EbId (IntMap BytesSize)) , toCopyBytesSize :: !BytesSize , @@ -224,6 +260,7 @@ emptyLeiosOutstanding = Map.empty Map.empty Map.empty + Map.empty 0 0 @@ -240,6 +277,8 @@ prettyLeiosOutstanding x = "requestedBytesSize = " ++ show requestedBytesSize , "missingEbTxs = " ++ unwords [ (prettyEbId k ++ "__" ++ show (IntMap.size v)) | (k, v) <- Map.toList missingEbTxs ] + , + "blockingPerEb = " ++ unwords [ (prettyEbId k ++ "__" ++ show c) | (k, c) <- Map.toList blockingPerEb ] , "toCopy = " ++ unwords [ (prettyEbId k ++ "__" ++ show (IntMap.size v)) | (k, v) <- Map.toList toCopy ] , @@ -260,6 +299,8 @@ prettyLeiosOutstanding x = requestedBytesSize , missingEbTxs + , + blockingPerEb , toCopy , diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index cbd8c95479..cf7fb0b07e 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -49,6 +49,9 @@ echo "Ports: ${PORT1} ${PORT2} ${PORT3}" TMP_DIR=$(mktemp -d ${TMPDIR:-/tmp}/leios-october-demo.XXXXXX) echo "Using temporary directory for DB and logs: $TMP_DIR" +rm -f ./leios-run-tmp-dir +ln -s "$TMP_DIR" ./leios-run-tmp-dir + pushd "$CARDANO_NODE_PATH" > /dev/null ## From 4d7c1bc43a0eb97bfc309f2b73601999f712f6ee Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 15:42:05 -0700 Subject: [PATCH 102/119] leiosdemo202510: more interpretable packing of ebIds, for now --- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 7158ae3bde..7bc085ff42 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -50,10 +50,7 @@ type HASH = Hash.Blake2b_256 ebIdSlot :: EbId -> SlotNo ebIdSlot (MkEbId y) = - SlotNo (fromIntegral (y - minBound :: Int) `Bits.unsafeShiftR` 20 :: Word64) - -ebIdBitWidthOfSlot :: Int -ebIdBitWidthOfSlot = 20 + SlotNo (fromIntegral y `div` 1000) ebIdToPoint :: EbId -> LeiosEbBodies -> Maybe LeiosPoint ebIdToPoint (MkEbId i) x = @@ -70,14 +67,14 @@ ebIdFromPoint p x = case IntMap.lookup islot (Leios.ebPoints x) of Just m -> case Map.lookup ebHash m of Just y -> (y, Nothing) - Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) - Map.size m - Nothing -> gen $ MkEbId $ zero + (2^ebIdBitWidthOfSlot - 1) + Nothing -> gen $ MkEbId $ zero + 99 - Map.size m + Nothing -> gen $ MkEbId $ zero + 99 where MkLeiosPoint ebSlot ebHash = p SlotNo wslot = ebSlot islot = fromIntegral (wslot :: Word64) - zero = fromIntegral (wslot `Bits.unsafeShiftL` ebIdBitWidthOfSlot) + minBound :: Int + zero = fromIntegral (wslot * 1000) :: Int gen y = let !x' = x { From b635ebd3c7a235131fde1f96ab04deabf61fac5e Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 17:50:24 -0700 Subject: [PATCH 103/119] leiosdemo202510: LeiosNotify server in node, but DB locked :/ --- .../Cardano/Tools/ImmDBServer/Diffusion.hs | 2 + .../Ouroboros/Consensus/Network/NodeToNode.hs | 17 +- .../Ouroboros/Consensus/NodeKernel.hs | 27 +- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 282 +++++++++++++----- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 7 + scripts/leios-demo/leios-october-demo.sh | 12 +- 6 files changed, 258 insertions(+), 89 deletions(-) diff --git a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs index 5117240995..577410cddb 100644 --- a/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs +++ b/ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/ImmDBServer/Diffusion.hs @@ -117,8 +117,10 @@ run immDBDir sockAddr cfg getSlotDelay leiosDbFile leiosSchedule = withRegistry True -> pure () Leios.MkSomeLeiosDb leiosDb <- Leios.newLeiosDbConnectionIO leiosDbFile leiosEbBodies <- LeiosLogic.loadEbBodies leiosDb + leiosWriteLock <- MVar.newMVar () fmap LeiosLogic.MkSomeLeiosFetchContext $ LeiosLogic.newLeiosFetchContext + leiosWriteLock leiosDb (pure leiosEbBodies) ImmutableDB.withDB diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index a6bb1dc09f..21b23db99c 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -48,6 +48,7 @@ import Codec.CBOR.Encoding (Encoding) import qualified Codec.CBOR.Encoding as CBOR import Codec.CBOR.Read (DeserialiseFailure) import qualified Control.Concurrent.Class.MonadMVar as MVar +import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM import qualified Control.Concurrent.Class.MonadSTM.Strict.TVar as TVar.Unchecked import Control.Monad.Class.MonadTime.SI (MonadTime) import Control.Monad.Class.MonadTimer.SI (MonadTimer) @@ -351,9 +352,14 @@ mkHandlers pure (offers1, offers2') void $ MVar.tryPutMVar getLeiosReady () ) - , hLeiosNotifyServer = \_version _peer -> - leiosNotifyServerPeer - (let loop = do threadDelay (60 :: DiffTime); loop in loop) -- TODO + , hLeiosNotifyServer = \_version peer -> Effect $ do + var <- StrictSTM.newTVarIO Map.empty + MVar.modifyMVar_ getLeiosNotifications $ \x -> do + let x' = Map.insert (Leios.MkPeerId peer) var x + pure x' + pure + $ leiosNotifyServerPeer + (Leios.nextLeiosNotification (getLeiosEbBodies, var)) , hLeiosFetchClient = \_version controlMessageSTM peer -> toLeiosFetchClientPeerPipelined $ Effect $ do Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection -- TODO share DB connection for same peer? reqVar <- @@ -370,7 +376,7 @@ mkHandlers $ leiosFetchClientPeerPipelined $ Leios.nextLeiosFetchClientCommand ((== Terminate) <$> controlMessageSTM) - (getLeiosWriteLock, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady) + (getLeiosWriteLock, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady, getLeiosNotifications) db (Leios.MkPeerId peer) reqVar @@ -378,6 +384,7 @@ mkHandlers Leios.MkSomeLeiosDb db <- getLeiosNewDbConnection leiosFetchContext <- Leios.newLeiosFetchContext + getLeiosWriteLock db (MVar.readMVar getLeiosEbBodies) pure $ leiosFetchServerPeer @@ -385,7 +392,7 @@ mkHandlers } where NodeKernel {getChainDB, getMempool, getTopLevelConfig, getTracers = tracers, getPeerSharingAPI, getGsmState} = nodeKernel - NodeKernel {getLeiosNewDbConnection, getLeiosPeersVars, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady, getLeiosWriteLock} = nodeKernel + NodeKernel {getLeiosNewDbConnection, getLeiosNotifications, getLeiosPeersVars, getLeiosEbBodies, getLeiosOutstanding, getLeiosReady, getLeiosWriteLock} = nodeKernel {------------------------------------------------------------------------------- Codecs diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index 1cdc520b8f..e7166cf37c 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -132,8 +132,7 @@ import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar import Data.Map (Map) import qualified Data.Map as Map --- import qualified Data.Set as Set - +import Data.Sequence (Seq) import LeiosDemoTypes (LeiosEbBodies, LeiosOutstanding, LeiosPeerVars, SomeLeiosDb) import qualified LeiosDemoTypes as Leios import qualified LeiosDemoLogic as Leios @@ -220,6 +219,14 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel { -- -- INVARIANT: never acquire 'MVar' while holding this lock. , getLeiosWriteLock :: MVar m () + , getLeiosNotifications :: + MVar m + (Map + (Leios.PeerId (ConnectionId addrNTN)) + (StrictSTM.StrictTVar m + (Map SlotNo (Seq Leios.LeiosNotification)) + ) + ) } @@ -382,6 +389,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers getLeiosOutstanding <- MVar.newMVar Leios.emptyLeiosOutstanding -- TODO init from DB getLeiosReady <- MVar.newEmptyMVar getLeiosWriteLock <- MVar.newMVar () + getLeiosNotifications <- MVar.newMVar Map.empty getLeiosCopyReady <- MVar.newEmptyMVar @@ -390,20 +398,24 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers leiosPeersVars <- MVar.readMVar getLeiosPeersVars offerings <- mapM (MVar.readMVar . Leios.offerings) leiosPeersVars ebBodies <- MVar.readMVar getLeiosEbBodies - (newDecisions, newCopy, _xxx, _yyy) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do + (newDecisions, newCopy, newNotifications) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do let (!outstanding', newDecisions) = Leios.leiosFetchLogicIteration Leios.demoLeiosFetchStaticEnv (ebBodies, offerings) outstanding let newCopy = Leios.toCopyCount outstanding' /= Leios.toCopyCount outstanding - pure (outstanding', (newDecisions, newCopy, outstanding, outstanding')) + let newNotifications = + Map.keys + $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' + pure (outstanding', (newDecisions, newCopy, newNotifications)) let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" {- ++ "\n" ++ "leiosOfferings: " ++ unwords [ Leios.prettyEbId ebId | (_peer, (_offers1, offers2)) <- Map.toList offerings, ebId <- Set.toList offers2 ] ++ "\n" ++ "leiosEbBodies: " ++ Leios.prettyLeiosEbBodies ebBodies ++ "\n" ++ "leiosOutstanding: " ++ Leios.prettyLeiosOutstanding xxx ++ "\n" ++ "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" -} + ++ "\n" ++ "leiosNotifications: " ++ unwords (map Leios.prettyEbId newNotifications) ++ "\n" {- forM_ newRequests $ \perPeer -> forM_ perPeer $ \case Leios.LeiosBlockRequest _ -> pure () @@ -423,7 +435,11 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers () <- MVar.takeMVar getLeiosCopyReady traceM $ "leiosCopy: running " ++ show i t1 <- getMonotonicTimeNSec - moreTodo <- Leios.doCacheCopy db (getLeiosWriteLock, getLeiosOutstanding) (500 * 10^(3 :: Int)) -- TODO magic number + moreTodo <- + Leios.doCacheCopy + db + (getLeiosWriteLock, getLeiosOutstanding, getLeiosNotifications) + (500 * 10^(3 :: Int)) -- TODO magic number t2 <- getMonotonicTimeNSec traceM $ "leiosCopy: done " ++ show (i, (t2 - t1) `div` (10^(6 :: Int))) void $ MVar.tryPutMVar getLeiosReady () @@ -455,6 +471,7 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers , getLeiosOutstanding , getLeiosReady , getLeiosWriteLock + , getLeiosNotifications } where blockForgingController :: InternalState m remotePeer localPeer blk diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 7bc085ff42..634b986356 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -1,4 +1,5 @@ {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} @@ -41,9 +42,10 @@ import qualified Data.Vector.Mutable as MV import Data.Word (Word16, Word64) import qualified Database.SQLite3.Direct as DB import Debug.Trace (traceM) +import qualified LeiosDemoOnlyTestNotify as LN import qualified LeiosDemoOnlyTestFetch as LF import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosOutstanding, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosFetchStaticEnv, LeiosTx (..), PeerId (..), TxHash (..)) -import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..)) +import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..), LeiosNotification (..)) import qualified LeiosDemoTypes as Leios type HASH = Hash.Blake2b_256 @@ -144,27 +146,34 @@ data LeiosFetchContext stmt m = MkLeiosFetchContext { leiosDb :: !(LeiosDb stmt m) , leiosEbBuffer :: !(MV.MVector (PrimState m) (TxHash, BytesSize)) , leiosEbTxsBuffer :: !(MV.MVector (PrimState m) LeiosTx) + , leiosWriteLock :: !(MVar m ()) , readLeiosEbBodies :: !(m LeiosEbBodies) } newLeiosFetchContext :: PrimMonad m => + MVar m () + -> LeiosDb stmt m -> m LeiosEbBodies -> m (LeiosFetchContext stmt m) -newLeiosFetchContext leiosDb readLeiosEbBodies = do +newLeiosFetchContext leiosWriteLock leiosDb readLeiosEbBodies = do -- each LeiosFetch server calls this when it initializes leiosEbBuffer <- MV.new Leios.maxEbItems leiosEbTxsBuffer <- MV.new Leios.maxEbItems - pure MkLeiosFetchContext { leiosDb, leiosEbBuffer, leiosEbTxsBuffer, readLeiosEbBodies} + pure MkLeiosFetchContext { leiosDb, leiosEbBuffer, leiosEbTxsBuffer, leiosWriteLock, readLeiosEbBodies} ----- leiosFetchHandler :: + ( PrimMonad m + , + MonadMVar m + ) => LeiosFetchContext stmt m -> @@ -177,29 +186,42 @@ leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case traceM $ "MsgLeiosBlockTxsRequest " <> Leios.prettyLeiosPoint p LF.MsgLeiosBlockTxs <$> msgLeiosBlockTxsRequest leiosContext p bitmaps -msgLeiosBlockRequest :: PrimMonad m => LeiosFetchContext stmt m -> LeiosPoint -> m LeiosEb +msgLeiosBlockRequest :: + ( + MonadMVar m + , + PrimMonad m + ) + => + LeiosFetchContext stmt m + -> + LeiosPoint + -> + m LeiosEb msgLeiosBlockRequest leiosContext p = do - let MkLeiosFetchContext {leiosDb = db, leiosEbBuffer = buf, readLeiosEbBodies} = leiosContext + let MkLeiosFetchContext {leiosDb = db, leiosEbBuffer = buf, leiosWriteLock, readLeiosEbBodies} = leiosContext (ebId, mbLeiosEbBodies') <- readLeiosEbBodies <&> ebIdFromPoint p case mbLeiosEbBodies' of Nothing -> pure () Just _ -> error "Unrecognized Leios point" - -- get the EB items - dbExec db (fromString "BEGIN") - stmt <- dbPrepare db (fromString sql_lookup_ebBodies) - dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) - let loop !i = - dbStep db stmt >>= \case - DB.Done -> do - dbFinalize db stmt - pure i - DB.Row -> do - txHashBytes <- dbColumnBlob db stmt 0 - txBytesSize <- fromIntegral <$> dbColumnInt64 db stmt 1 - MV.write buf i (MkTxHash txHashBytes, txBytesSize) - loop (i+1) - n <- loop 0 - dbExec db (fromString "COMMIT") + n <- MVar.withMVar leiosWriteLock $ \() -> do + -- get the EB items + dbExec db (fromString "BEGIN") + stmt <- dbPrepare db (fromString sql_lookup_ebBodies) + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + let loop !i = + dbStep db stmt >>= \case + DB.Done -> do + dbFinalize db stmt + pure i + DB.Row -> do + txHashBytes <- dbColumnBlob db stmt 0 + txBytesSize <- fromIntegral <$> dbColumnInt64 db stmt 1 + MV.write buf i (MkTxHash txHashBytes, txBytesSize) + loop (i+1) + n <- loop 0 + dbExec db (fromString "COMMIT") + pure n v <- V.freeze $ MV.slice 0 n buf pure $ MkLeiosEb v @@ -211,7 +233,11 @@ sql_lookup_ebBodies = \" msgLeiosBlockTxsRequest :: + ( + MonadMVar m + , PrimMonad m + ) => LeiosFetchContext stmt m -> @@ -221,7 +247,7 @@ msgLeiosBlockTxsRequest :: -> m (V.Vector LeiosTx) msgLeiosBlockTxsRequest leiosContext p bitmaps = do - let MkLeiosFetchContext {leiosDb = db, leiosEbTxsBuffer = buf, readLeiosEbBodies} = leiosContext + let MkLeiosFetchContext {leiosDb = db, leiosEbTxsBuffer = buf, leiosWriteLock, readLeiosEbBodies} = leiosContext (ebId, mbLeiosEbBodies') <- readLeiosEbBodies <&> ebIdFromPoint p case mbLeiosEbBodies' of Nothing -> pure () @@ -242,35 +268,37 @@ msgLeiosBlockTxsRequest leiosContext p bitmaps = do Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) txOffsets = unfoldr nextOffset bitmaps - -- fill in-memory table - dbExec db (fromString "BEGIN") - do - stmt <- dbPrepare db (fromString sql_insert_memTxPoints) - dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) - forM_ txOffsets $ \txOffset -> do - dbBindInt64 db stmt 2 (fromIntegral txOffset) - dbStep1 db stmt - dbReset db stmt - dbFinalize db stmt - -- get txBytess - stmt <- dbPrepare db (fromString sql_retrieve_from_ebTxs) - n <- (\f -> foldM f 0 txOffsets) $ \i txOffset -> do - dbStep db stmt >>= \case - DB.Done -> do - dbFinalize db stmt - pure i - DB.Row -> do - txOffset' <- dbColumnInt64 db stmt 0 - txBytes <- dbColumnBlob db stmt 1 - when (fromIntegral txOffset /= txOffset') $ do - error $ "Missing offset " ++ show (txOffset, txOffset') - tx <- case decodeFullDecoder' (fromString "txBytes column") Leios.decodeLeiosTx txBytes of - Left err -> error $ "Failed to deserialize txBytes column: " ++ Leios.prettyLeiosPoint p ++ " " ++ show (txOffset', err) - Right tx -> pure tx - MV.write buf i tx - pure $! (i + 1) - dbExec db (fromString sql_flush_memTxPoints) - dbExec db (fromString "COMMIT") + n <- MVar.withMVar leiosWriteLock $ \() -> do + -- fill in-memory table + dbExec db (fromString "BEGIN") + do + stmt <- dbPrepare db (fromString sql_insert_memTxPoints) + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + forM_ txOffsets $ \txOffset -> do + dbBindInt64 db stmt 2 (fromIntegral txOffset) + dbStep1 db stmt + dbReset db stmt + dbFinalize db stmt + -- get txBytess + stmt <- dbPrepare db (fromString sql_retrieve_from_ebTxs) + n <- (\f -> foldM f 0 txOffsets) $ \i txOffset -> do + dbStep db stmt >>= \case + DB.Done -> do + dbFinalize db stmt + pure i + DB.Row -> do + txOffset' <- dbColumnInt64 db stmt 0 + txBytes <- dbColumnBlob db stmt 1 + when (fromIntegral txOffset /= txOffset') $ do + error $ "Missing offset " ++ show (txOffset, txOffset') + tx <- case decodeFullDecoder' (fromString "txBytes column") Leios.decodeLeiosTx txBytes of + Left err -> error $ "Failed to deserialize txBytes column: " ++ Leios.prettyLeiosPoint p ++ " " ++ show (txOffset', err) + Right tx -> pure tx + MV.write buf i tx + pure $! (i + 1) + dbExec db (fromString sql_flush_memTxPoints) + dbExec db (fromString "COMMIT") + pure n V.freeze $ MV.slice 0 n buf {- | For example @@ -611,7 +639,7 @@ nextLeiosFetchClientCommand :: forall pid stmt m. => StrictSTM.STM m Bool -> - (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m (), MVar m (Map (PeerId pid) (StrictTVar m (Map SlotNo (Seq LeiosNotification))))) -> LeiosDb stmt m -> @@ -664,9 +692,11 @@ msgLeiosBlock :: Ord pid , MonadMVar m + , + MonadSTM m ) => - (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m (), MVar m (Map (PeerId pid) (StrictTVar m (Map SlotNo (Seq LeiosNotification))))) -> LeiosDb stmt m -> @@ -677,7 +707,7 @@ msgLeiosBlock :: LeiosEb -> m () -msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req eb = do +msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req eb = do -- validate it let MkLeiosBlockRequest p ebBytesSize = req traceM $ "MsgLeiosBlock " <> Leios.prettyLeiosPoint p @@ -765,6 +795,17 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req e } pure outstanding' void $ MVar.tryPutMVar readyVar () + when novel $ do + vars <- MVar.readMVar notificationVars + forM_ vars $ \var -> StrictSTM.atomically $ do + x <- StrictSTM.readTVar var + let !x' = + Map.insertWith + (<>) + (ebIdSlot ebId) + (Seq.singleton (LeiosOfferBlock ebId ebBytesSize)) + x + StrictSTM.writeTVar var x' sql_insert_ebBody :: String sql_insert_ebBody = @@ -783,9 +824,21 @@ msgLeiosBlockTxs :: Ord pid , MonadMVar m + , + MonadSTM m ) => - (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m ()) + ( + MVar m () + , + MVar m LeiosEbBodies + , + MVar m (LeiosOutstanding pid) + , + MVar m () + , + MVar m (Map (PeerId pid) (StrictTVar m (Map SlotNo (Seq LeiosNotification)))) + ) -> LeiosDb stmt m -> @@ -796,7 +849,7 @@ msgLeiosBlockTxs :: V.Vector LeiosTx -> m () -msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId req txs = do +msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req txs = do traceM $ Leios.prettyLeiosBlockTxsRequest req -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req @@ -849,7 +902,7 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re dbReset db stmtTxCache dbExec db (fromString "COMMIT") -- update NodeKernel state - MVar.modifyMVar_ outstandingVar $ \outstanding -> do + newNotifications <- MVar.modifyMVar outstandingVar $ \outstanding -> do let (requestedTxPeers', cachedTxs', txOffsetss', txsBytesSize) = (\f -> V.foldl f @@ -875,22 +928,18 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re accSz + BS.length txBytes ) let offsetsSet = IntSet.fromList offsets - beatOtherPeers = - -- the requests that this MsgLeiosBlockTxs was the first to - -- resolve - (`IntMap.restrictKeys` IntSet.fromList offsets) - $ Map.findWithDefault - IntMap.empty - ebId - (Leios.toCopy outstanding) - beatToCopy = - -- the currently scheduled 'toCopy' operations that this - -- MsgLeiosBlockTxs just won the race against - (`IntMap.restrictKeys` IntSet.fromList offsets) + checkBeat :: forall a. Map EbId (IntMap a) -> IntMap a + checkBeat x = + (`IntMap.restrictKeys` offsetsSet) $ Map.findWithDefault IntMap.empty ebId - (Leios.toCopy outstanding) + x + -- the requests that this MsgLeiosBlockTxs was the first to resolve + beatOtherPeers = checkBeat $ Leios.missingEbTxs outstanding + -- the currently scheduled 'toCopy' operations that this + -- MsgLeiosBlockTxs just won the race against + beatToCopy = checkBeat $ Leios.toCopy outstanding let !outstanding' = outstanding { Leios.cachedTxs = cachedTxs' , @@ -903,11 +952,11 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re Leios.txOffsetss = txOffsetss' , Leios.blockingPerEb = - if IntMap.null beatOtherPeers then Leios.blockingPerEb outstanding else + if IntMap.null beatOtherPeers && IntMap.null beatToCopy then Leios.blockingPerEb outstanding else Map.alter (\case Nothing -> Nothing - Just x -> delIf (==0) $ x - IntMap.size beatOtherPeers + Just x -> delIf (==0) $ x - IntMap.size beatOtherPeers - IntMap.size beatToCopy ) ebId (Leios.blockingPerEb outstanding) @@ -944,8 +993,21 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar) db peerId re Leios.toCopyCount = Leios.toCopyCount outstanding - IntMap.size beatToCopy } - pure outstanding' + let newNotifications = + (\ebIds -> + Map.fromList + [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) | x <- ebIds ] + ) + $ Map.keys + $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' + pure (outstanding', newNotifications) void $ MVar.tryPutMVar readyVar () + when (not $ Map.null newNotifications) $ do + vars <- MVar.readMVar notificationVars + forM_ vars $ \var -> StrictSTM.atomically $ do + x <- StrictSTM.readTVar var + let !x' = Map.unionWith (<>) x newNotifications + StrictSTM.writeTVar var x' sql_update_ebTx :: String sql_update_ebTx = @@ -962,10 +1024,26 @@ sql_insert_txCache = ----- doCacheCopy :: + ( MonadMVar m + , + MonadSTM m + ) => - LeiosDb stmt m -> (MVar m (), MVar m (LeiosOutstanding pid)) -> BytesSize -> m Bool -doCacheCopy db (writeLock, outstandingVar) bytesSize = do + LeiosDb stmt m + -> + ( + MVar m () + , + MVar m (LeiosOutstanding pid) + , + MVar m (Map (PeerId pid) (StrictTVar m (Map SlotNo (Seq LeiosNotification)))) + ) + -> + BytesSize + -> + m Bool +doCacheCopy db (writeLock, outstandingVar, notificationVars) bytesSize = do copied <- do outstanding <- MVar.readMVar outstandingVar MVar.withMVar writeLock $ \() -> do @@ -975,7 +1053,7 @@ doCacheCopy db (writeLock, outstandingVar) bytesSize = do dbFinalize db stmt dbExec db (fromString "COMMIT") pure x - MVar.modifyMVar outstandingVar $ \outstanding -> do + (moreTodo, newNotifications) <- MVar.modifyMVar outstandingVar $ \outstanding -> do let _ = copied :: Map EbId IntSet let usefulCopied = -- @copied@ might contain elements that were already accounted @@ -1008,7 +1086,21 @@ doCacheCopy db (writeLock, outstandingVar) bytesSize = do Leios.toCopyCount = Leios.toCopyCount outstanding - sum (Map.map IntMap.size usefulCopied) } - pure (outstanding', 0 /= Leios.toCopyCount outstanding') + let newNotifications = + (\ebIds -> + Map.fromList + [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) | x <- ebIds ] + ) + $ Map.keys + $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' + pure (outstanding', (0 /= Leios.toCopyCount outstanding', newNotifications)) + when (not $ Map.null newNotifications) $ do + vars <- MVar.readMVar notificationVars + forM_ vars $ \var -> StrictSTM.atomically $ do + x <- StrictSTM.readTVar var + let !x' = Map.unionWith (<>) x newNotifications + StrictSTM.writeTVar var x' + pure moreTodo where go1 stmt !accCopied !accBytesSize !acc | accBytesSize < bytesSize @@ -1044,3 +1136,39 @@ sql_copy_from_txCache = \SET txBytes = (SELECT txBytes FROM txCache WHERE txCache.txHashBytes = ebTxs.txHashBytes)\n\ \WHERE ebId = ? AND txOffset = ? AND txBytes IS NULL\n\ \" + +----- + +nextLeiosNotification :: + ( + MonadMVar m + , + MonadSTM m + ) + => + (MVar m LeiosEbBodies, StrictTVar m (Map SlotNo (Seq LeiosNotification))) + -> + m (LN.Message (LN.LeiosNotify LeiosPoint announcement) LN.StBusy LN.StIdle) +nextLeiosNotification (ebBodiesVar, var) = do + notification <- StrictSTM.atomically $ do + x <- StrictSTM.readTVar var + go1 x + ebBodies <- MVar.readMVar ebBodiesVar + let f ebId = case ebIdToPoint ebId ebBodies of + Nothing -> error "impossible!" + Just x -> x + pure $ case notification of + LeiosOfferBlock ebId ebBytesSize -> + LN.MsgLeiosBlockOffer (f ebId) ebBytesSize + LeiosOfferBlockTxs ebId -> + LN.MsgLeiosBlockTxsOffer (f ebId) + where + go1 = go2 . Map.maxViewWithKey + go2 = \case + Nothing -> StrictSTM.retry + Just ((_slotNo, Seq.Empty), x') -> go1 x' + Just ((slotNo, notification Seq.:<| notifications), x') -> do + StrictSTM.writeTVar var $ + if Seq.null notifications then x' else + Map.insert slotNo notifications x' + pure notification diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 77ac46a23a..8515e95e35 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -533,3 +533,10 @@ demoLeiosFetchStaticEnv = millionBase2 = 2^(20 :: Int) thousand :: Num a => a thousand = 10^(3 :: Int) + +----- + +data LeiosNotification = + LeiosOfferBlock EbId BytesSize + | + LeiosOfferBlockTxs EbId diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index cf7fb0b07e..774bf5ec23 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -81,7 +81,11 @@ EOF mkdir -p "$TMP_DIR/node-0/db" -CARDANO_NODE_CMD="${CARDANO_NODE} run \ +cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-0/leios.db" +sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' + +CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ + ${CARDANO_NODE} run \ --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ @@ -122,7 +126,11 @@ EOF mkdir -p "$TMP_DIR/node-1/db" -MOCKED_PEER_CMD="cabal run -- cardano-node run \ +cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-1/leios.db" +sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' + +MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ + ${CARDANO_NODE} run \ --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-1.json \ --database-path $TMP_DIR/node-1/db \ From 6e5d547feabab0131040bfa96c6309d92a3957ab Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 18:26:49 -0700 Subject: [PATCH 104/119] WIP HasCallStack for db --- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 1 + .../src/ouroboros-consensus/LeiosDemoTypes.hs | 92 +++++++++++++------ 2 files changed, 65 insertions(+), 28 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 634b986356..bed1bd44b2 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -46,6 +46,7 @@ import qualified LeiosDemoOnlyTestNotify as LN import qualified LeiosDemoOnlyTestFetch as LF import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosOutstanding, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosFetchStaticEnv, LeiosTx (..), PeerId (..), TxHash (..)) import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..), LeiosNotification (..)) +import LeiosDemoTypes (dbBindBlob, dbBindInt64, dbColumnBlob, dbColumnInt64, dbExec, dbFinalize, dbPrepare, dbReset, dbStep, dbStep1) import qualified LeiosDemoTypes as Leios type HASH = Hash.Blake2b_256 diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 8515e95e35..0ba90a7d3d 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -1,6 +1,7 @@ {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE Rank2Types #-} module LeiosDemoTypes (module LeiosDemoTypes) where @@ -31,6 +32,8 @@ import Data.String (fromString) import qualified Data.Vector as V import Data.Word (Word16, Word32, Word64) import qualified Database.SQLite3.Direct as DB +import GHC.Stack (HasCallStack) +import qualified GHC.Stack import qualified Numeric import Ouroboros.Consensus.Util (ShowProxy (..)) import Ouroboros.Consensus.Util.IOLike (IOLike) @@ -372,74 +375,107 @@ maxEbItems = data SomeLeiosDb m = forall stmt. MkSomeLeiosDb (LeiosDb stmt m) data LeiosDb stmt m = MkLeiosDb { - dbBindBlob :: !(stmt -> DB.ParamIndex -> ByteString -> m ()) + dbBindBlob_ :: !(HasCallStack => stmt -> DB.ParamIndex -> ByteString -> m ()) , - dbBindInt64 :: !(stmt -> DB.ParamIndex -> Int64 -> m ()) + dbBindInt64_ :: !(HasCallStack => stmt -> DB.ParamIndex -> Int64 -> m ()) , - dbColumnBlob :: !(stmt -> DB.ColumnIndex -> m ByteString) + dbColumnBlob_ :: !(HasCallStack => stmt -> DB.ColumnIndex -> m ByteString) , - dbColumnInt64 :: !(stmt -> DB.ColumnIndex -> m Int64) + dbColumnInt64_ :: !(HasCallStack => stmt -> DB.ColumnIndex -> m Int64) , - dbExec :: !(DB.Utf8 -> m ()) + dbExec_ :: !(HasCallStack => DB.Utf8 -> m ()) , - dbFinalize :: !(stmt -> m ()) + dbFinalize_ :: !(HasCallStack => stmt -> m ()) , - dbPrepare :: !(DB.Utf8 -> m stmt) + dbPrepare_ :: !(HasCallStack => DB.Utf8 -> m stmt) , - dbReset :: !(stmt -> m ()) + dbReset_ :: !(HasCallStack => stmt -> m ()) , - dbStep :: !(stmt -> m DB.StepResult) + dbStep_ :: !(HasCallStack => stmt -> m DB.StepResult) , - dbStep1 :: !(stmt -> m ()) + dbStep1_ :: !(HasCallStack => stmt -> m ()) } +dbBindBlob :: HasCallStack => LeiosDb stmt m -> stmt -> DB.ParamIndex -> ByteString -> m () +dbBindBlob = dbBindBlob_ + +dbBindInt64 :: HasCallStack => LeiosDb stmt m -> stmt -> DB.ParamIndex -> Int64 -> m () +dbBindInt64 = dbBindInt64_ + +dbColumnBlob :: HasCallStack => LeiosDb stmt m -> stmt -> DB.ColumnIndex -> m ByteString +dbColumnBlob = dbColumnBlob_ + +dbColumnInt64 :: HasCallStack => LeiosDb stmt m -> stmt -> DB.ColumnIndex -> m Int64 +dbColumnInt64 = dbColumnInt64_ + +dbExec :: HasCallStack => LeiosDb stmt m -> DB.Utf8 -> m () +dbExec = dbExec_ + +dbFinalize :: HasCallStack => LeiosDb stmt m -> stmt -> m () +dbFinalize = dbFinalize_ + +dbPrepare :: HasCallStack => LeiosDb stmt m -> DB.Utf8 -> m stmt +dbPrepare = dbPrepare_ + +dbReset :: HasCallStack => LeiosDb stmt m -> stmt -> m () +dbReset = dbReset_ + +dbStep :: HasCallStack => LeiosDb stmt m -> stmt -> m DB.StepResult +dbStep = dbStep_ + +dbStep1 :: HasCallStack => LeiosDb stmt m -> stmt -> m () +dbStep1 = dbStep1_ + leiosDbFromSqliteDirect :: DB.Database -> LeiosDb DB.Statement IO leiosDbFromSqliteDirect db = MkLeiosDb { - dbBindBlob = \stmt p v -> withDie $ DB.bindBlob stmt p v + dbBindBlob_ = \stmt p v -> withDie $ DB.bindBlob stmt p v , - dbBindInt64 = \stmt p v -> withDie $ DB.bindInt64 stmt p v + dbBindInt64_ = \stmt p v -> withDie $ DB.bindInt64 stmt p v , - dbColumnBlob = \stmt c -> DB.columnBlob stmt c + dbColumnBlob_ = \stmt c -> DB.columnBlob stmt c , - dbColumnInt64 = \stmt c -> DB.columnInt64 stmt c + dbColumnInt64_ = \stmt c -> DB.columnInt64 stmt c , - dbExec = \q -> withDieMsg $ DB.exec db q + dbExec_ = \q -> withDieMsg $ DB.exec db q , - dbFinalize = \stmt -> withDie $ DB.finalize stmt + dbFinalize_ = \stmt -> withDie $ DB.finalize stmt , - dbPrepare = \q -> withDieJust $ DB.prepare db q + dbPrepare_ = \q -> withDieJust $ DB.prepare db q , - dbReset = \stmt -> withDie $ DB.reset stmt + dbReset_ = \stmt -> withDie $ DB.reset stmt , - dbStep = \stmt -> withDie $ DB.stepNoCB stmt + dbStep_ = \stmt -> withDie $ DB.stepNoCB stmt , - dbStep1 = \stmt -> withDieDone $ DB.stepNoCB stmt + dbStep1_ = \stmt -> withDieDone $ DB.stepNoCB stmt } -withDiePoly :: Show b => (e -> b) -> IO (Either e a) -> IO a +withDiePoly :: (HasCallStack, Show b) => (e -> b) -> IO (Either e a) -> IO a withDiePoly f io = io >>= \case - Left e -> die $ "LeiosDb: " ++ show (f e) + Left e -> dieStack $ "LeiosDb: " ++ show (f e) Right x -> pure x -withDieMsg :: IO (Either (DB.Error, DB.Utf8) a) -> IO a +withDieMsg :: HasCallStack => IO (Either (DB.Error, DB.Utf8) a) -> IO a withDieMsg = withDiePoly snd -withDie :: IO (Either DB.Error a) -> IO a +withDie :: HasCallStack => IO (Either DB.Error a) -> IO a withDie = withDiePoly id -withDieJust :: IO (Either DB.Error (Maybe a)) -> IO a +withDieJust :: HasCallStack => IO (Either DB.Error (Maybe a)) -> IO a withDieJust io = withDie io >>= \case - Nothing -> die $ "LeiosDb: [Just] " ++ "impossible!" + Nothing -> dieStack $ "LeiosDb: [Just] " ++ "impossible!" Just x -> pure x -withDieDone :: IO (Either DB.Error DB.StepResult) -> IO () +withDieDone :: HasCallStack => IO (Either DB.Error DB.StepResult) -> IO () withDieDone io = withDie io >>= \case - DB.Row -> die $ "LeiosDb: [Done] " ++ "impossible!" + DB.Row -> dieStack $ "LeiosDb: [Done] " ++ "impossible!" DB.Done -> pure () +dieStack :: HasCallStack => String -> IO a +dieStack s = dieStack $ s ++ "\n\n" ++ GHC.Stack.prettyCallStack GHC.Stack.callStack + ----- demoNewLeiosDbConnectionIO :: IO (SomeLeiosDb IO) From 41fbed6740b1830fc77c2e981b3c1a1363b99124 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 19:14:06 -0700 Subject: [PATCH 105/119] WIP node-0 freezing??? --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 2 +- .../Ouroboros/Consensus/NodeKernel.hs | 21 +------ .../src/ouroboros-consensus/LeiosDemoLogic.hs | 58 +++++++++++-------- scripts/leios-demo/leios-october-demo.sh | 2 +- 4 files changed, 40 insertions(+), 43 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 21b23db99c..a39e214688 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -355,7 +355,7 @@ mkHandlers , hLeiosNotifyServer = \_version peer -> Effect $ do var <- StrictSTM.newTVarIO Map.empty MVar.modifyMVar_ getLeiosNotifications $ \x -> do - let x' = Map.insert (Leios.MkPeerId peer) var x + let !x' = Map.insert (Leios.MkPeerId peer) var x pure x' pure $ leiosNotifyServerPeer diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs index e7166cf37c..b9f44dae08 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs @@ -398,31 +398,16 @@ initNodeKernel args@NodeKernelArgs { registry, cfg, tracers leiosPeersVars <- MVar.readMVar getLeiosPeersVars offerings <- mapM (MVar.readMVar . Leios.offerings) leiosPeersVars ebBodies <- MVar.readMVar getLeiosEbBodies - (newDecisions, newCopy, newNotifications) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do + (newDecisions, newCopy) <- MVar.modifyMVar getLeiosOutstanding $ \outstanding -> do let (!outstanding', newDecisions) = Leios.leiosFetchLogicIteration Leios.demoLeiosFetchStaticEnv (ebBodies, offerings) outstanding let newCopy = Leios.toCopyCount outstanding' /= Leios.toCopyCount outstanding - let newNotifications = - Map.keys - $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' - pure (outstanding', (newDecisions, newCopy, newNotifications)) + pure (outstanding', (newDecisions, newCopy)) let newRequests = Leios.packRequests Leios.demoLeiosFetchStaticEnv ebBodies newDecisions - traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" {- ++ "\n" ++ - "leiosOfferings: " ++ unwords [ Leios.prettyEbId ebId | (_peer, (_offers1, offers2)) <- Map.toList offerings, ebId <- Set.toList offers2 ] ++ "\n" ++ - "leiosEbBodies: " ++ Leios.prettyLeiosEbBodies ebBodies ++ "\n" ++ - "leiosOutstanding: " ++ Leios.prettyLeiosOutstanding xxx ++ "\n" ++ - "leiosOutstanding': " ++ Leios.prettyLeiosOutstanding yyy ++ "\n" -} - ++ "\n" ++ "leiosNotifications: " ++ unwords (map Leios.prettyEbId newNotifications) ++ "\n" -{- - forM_ newRequests $ \perPeer -> forM_ perPeer $ \case - Leios.LeiosBlockRequest _ -> pure () - Leios.LeiosBlockTxsRequest (Leios.MkLeiosBlockTxsRequest _p _bitmaps txHashes) -> do - forM_ txHashes $ \txHash -> do - traceM $ "leiosReqTxHash: " ++ Leios.prettyTxHash txHash --} + traceM $ "leiosFetchLogic: " ++ show (sum (fmap length newRequests)) ++ " new reqs, " ++ show newCopy ++ " new copy" (\f -> sequence_ $ Map.intersectionWith f leiosPeersVars newRequests) $ \vars reqs -> atomically $ do StrictSTM.modifyTVar (Leios.requestsToSend vars) (<> reqs) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index bed1bd44b2..b759685fc1 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -181,11 +181,15 @@ leiosFetchHandler :: LF.LeiosFetchRequestHandler LeiosPoint LeiosEb LeiosTx m leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case LF.MsgLeiosBlockRequest p -> do - traceM $ "MsgLeiosBlockRequest " <> Leios.prettyLeiosPoint p - LF.MsgLeiosBlock <$> msgLeiosBlockRequest leiosContext p + traceM $ "[start] MsgLeiosBlockRequest " <> Leios.prettyLeiosPoint p + x <- msgLeiosBlockRequest leiosContext p + traceM $ "[done] MsgLeiosBlockRequest " <> Leios.prettyLeiosPoint p + pure $ LF.MsgLeiosBlock x LF.MsgLeiosBlockTxsRequest p bitmaps -> do - traceM $ "MsgLeiosBlockTxsRequest " <> Leios.prettyLeiosPoint p - LF.MsgLeiosBlockTxs <$> msgLeiosBlockTxsRequest leiosContext p bitmaps + traceM $ "[start] MsgLeiosBlockTxsRequest " <> Leios.prettyLeiosPoint p + x <- msgLeiosBlockTxsRequest leiosContext p bitmaps + traceM $ "[done] MsgLeiosBlockTxsRequest " <> Leios.prettyLeiosPoint p + pure $ LF.MsgLeiosBlockTxs x msgLeiosBlockRequest :: ( @@ -711,7 +715,7 @@ msgLeiosBlock :: msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req eb = do -- validate it let MkLeiosBlockRequest p ebBytesSize = req - traceM $ "MsgLeiosBlock " <> Leios.prettyLeiosPoint p + traceM $ "[start] MsgLeiosBlock " <> Leios.prettyLeiosPoint p do let MkLeiosPoint _ebSlot ebHash = p let ebBytes :: ByteString @@ -797,8 +801,10 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVar pure outstanding' void $ MVar.tryPutMVar readyVar () when novel $ do + traceM $ "leiosNotificationsBlock: " ++ Leios.prettyEbId ebId vars <- MVar.readMVar notificationVars forM_ vars $ \var -> StrictSTM.atomically $ do + traceM $ "leiosNotificationsBlock!: " ++ Leios.prettyEbId ebId x <- StrictSTM.readTVar var let !x' = Map.insertWith @@ -807,6 +813,7 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVar (Seq.singleton (LeiosOfferBlock ebId ebBytesSize)) x StrictSTM.writeTVar var x' + traceM $ "[done] MsgLeiosBlock " <> Leios.prettyLeiosPoint p sql_insert_ebBody :: String sql_insert_ebBody = @@ -851,7 +858,7 @@ msgLeiosBlockTxs :: -> m () msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req txs = do - traceM $ Leios.prettyLeiosBlockTxsRequest req + traceM $ "[start] " ++ Leios.prettyLeiosBlockTxsRequest req -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req -- forM_ txHashes $ \txHash -> do @@ -995,20 +1002,24 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notification Leios.toCopyCount outstanding - IntMap.size beatToCopy } let newNotifications = - (\ebIds -> - Map.fromList - [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) | x <- ebIds ] - ) - $ Map.keys + Map.keys $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' pure (outstanding', newNotifications) void $ MVar.tryPutMVar readyVar () - when (not $ Map.null newNotifications) $ do + when (not $ null newNotifications) $ do + let notifications = + Map.fromList + $ [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) + | x <- newNotifications + ] + traceM $ "leiosNotificationsBlockTxs: " ++ unwords (map Leios.prettyEbId newNotifications) vars <- MVar.readMVar notificationVars forM_ vars $ \var -> StrictSTM.atomically $ do + traceM $ "leiosNotificationsBlockTxs!: " ++ unwords (map Leios.prettyEbId newNotifications) x <- StrictSTM.readTVar var - let !x' = Map.unionWith (<>) x newNotifications + let !x' = Map.unionWith (<>) x notifications StrictSTM.writeTVar var x' + traceM $ "[done] " ++ Leios.prettyLeiosBlockTxsRequest req sql_update_ebTx :: String sql_update_ebTx = @@ -1088,18 +1099,21 @@ doCacheCopy db (writeLock, outstandingVar, notificationVars) bytesSize = do Leios.toCopyCount outstanding - sum (Map.map IntMap.size usefulCopied) } let newNotifications = - (\ebIds -> - Map.fromList - [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) | x <- ebIds ] - ) - $ Map.keys + Map.keys $ Leios.blockingPerEb outstanding `Map.difference` Leios.blockingPerEb outstanding' pure (outstanding', (0 /= Leios.toCopyCount outstanding', newNotifications)) - when (not $ Map.null newNotifications) $ do + when (not $ null newNotifications) $ do + let notifications = + Map.fromList + $ [ (ebIdSlot x, Seq.singleton (LeiosOfferBlockTxs x)) + | x <- newNotifications + ] + traceM $ "leiosNotificationsCopy: " ++ unwords (map Leios.prettyEbId newNotifications) vars <- MVar.readMVar notificationVars forM_ vars $ \var -> StrictSTM.atomically $ do + traceM $ "leiosNotificationsCopy!: " ++ unwords (map Leios.prettyEbId newNotifications) x <- StrictSTM.readTVar var - let !x' = Map.unionWith (<>) x newNotifications + let !x' = Map.unionWith (<>) x notifications StrictSTM.writeTVar var x' pure moreTodo where @@ -1151,9 +1165,7 @@ nextLeiosNotification :: -> m (LN.Message (LN.LeiosNotify LeiosPoint announcement) LN.StBusy LN.StIdle) nextLeiosNotification (ebBodiesVar, var) = do - notification <- StrictSTM.atomically $ do - x <- StrictSTM.readTVar var - go1 x + notification <- StrictSTM.atomically $ StrictSTM.readTVar var >>= go1 ebBodies <- MVar.readMVar ebBodiesVar let f ebId = case ebIdToPoint ebId ebBodies of Nothing -> error "impossible!" diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 774bf5ec23..d5536c3154 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -127,7 +127,7 @@ EOF mkdir -p "$TMP_DIR/node-1/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-1/leios.db" -sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' +sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ ${CARDANO_NODE} run \ From ff77ac381581ad1f7582e128671e5e0eb3b30851 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 19:14:31 -0700 Subject: [PATCH 106/119] WIP change host-addr? --- scripts/leios-demo/leios-october-demo.sh | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index d5536c3154..0af4e4c249 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -90,9 +90,9 @@ CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ --socket-path node-0.socket \ - --host-addr 0.0.0.0 --port ${PORT2}" + --host-addr 127.0.0.1 --port ${PORT2}" -echo "Command: $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" +echo "Command (Node 0): $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" $CARDANO_NODE_CMD &> "$TMP_DIR/cardano-node-0.log" & @@ -135,7 +135,7 @@ MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ --topology topology-node-1.json \ --database-path $TMP_DIR/node-1/db \ --socket-path node-1.socket \ - --host-addr 0.0.0.0 --port ${PORT3}" + --host-addr 127.0.0.1 --port ${PORT3}" echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" From 39732522ede4fb0aa533187be9433b84e0aab80b Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 20:15:52 -0700 Subject: [PATCH 107/119] WIP fix missing finalize and dieStack = dieStack :'( --- .../src/ouroboros-consensus/LeiosDemoLogic.hs | 196 +++++++----------- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 19 +- 2 files changed, 93 insertions(+), 122 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index b759685fc1..c10fa37455 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -46,8 +46,9 @@ import qualified LeiosDemoOnlyTestNotify as LN import qualified LeiosDemoOnlyTestFetch as LF import LeiosDemoTypes (BytesSize, EbHash (..), EbId (..), LeiosEbBodies, LeiosOutstanding, LeiosPoint (..), LeiosDb (..), LeiosEb (..), LeiosFetchStaticEnv, LeiosTx (..), PeerId (..), TxHash (..)) import LeiosDemoTypes (LeiosBlockRequest (..), LeiosBlockTxsRequest (..), LeiosFetchRequest (..), LeiosNotification (..)) -import LeiosDemoTypes (dbBindBlob, dbBindInt64, dbColumnBlob, dbColumnInt64, dbExec, dbFinalize, dbPrepare, dbReset, dbStep, dbStep1) +import LeiosDemoTypes (dbBindBlob, dbBindInt64, dbColumnBlob, dbColumnInt64, dbExec, dbReset, dbStep, dbStep1, dbWithBEGIN, dbWithPrepare) import qualified LeiosDemoTypes as Leios +import Ouroboros.Consensus.Util.IOLike (IOLike) type HASH = Hash.Blake2b_256 @@ -107,24 +108,20 @@ ebIdFromPointM mvar p = ----- -loadEbBodies :: Monad m => LeiosDb stmt m -> m LeiosEbBodies +loadEbBodies :: IOLike m => LeiosDb stmt m -> m LeiosEbBodies loadEbBodies db = do - dbExec db (fromString "BEGIN") - stmt <- dbPrepare db (fromString sql_scan_ebId) - let loop !ps !qs = - dbStep db stmt >>= \case - DB.Done -> do - dbFinalize db stmt - pure (ps, qs) - DB.Row -> do - ebSlot <- fromIntegral <$> dbColumnInt64 db stmt 0 - ebHash <- MkEbHash <$> dbColumnBlob db stmt 1 - ebId <- fromIntegral <$> dbColumnInt64 db stmt 2 - loop - (IntMap.insertWith Map.union ebSlot (Map.singleton ebHash (MkEbId ebId)) ps) - (IntMap.insert ebId ebHash qs) - (ps, qs) <- loop IntMap.empty IntMap.empty - dbExec db (fromString "COMMIT") + (ps, qs) <- dbWithBEGIN db $ dbWithPrepare db (fromString sql_scan_ebId) $ \stmt -> do + let loop !ps !qs = + dbStep db stmt >>= \case + DB.Done -> pure (ps, qs) + DB.Row -> do + ebSlot <- fromIntegral <$> dbColumnInt64 db stmt 0 + ebHash <- MkEbHash <$> dbColumnBlob db stmt 1 + ebId <- fromIntegral <$> dbColumnInt64 db stmt 2 + loop + (IntMap.insertWith Map.union ebSlot (Map.singleton ebHash (MkEbId ebId)) ps) + (IntMap.insert ebId ebHash qs) + loop IntMap.empty IntMap.empty pure Leios.emptyLeiosEbBodies { Leios.ebPoints = ps , @@ -170,11 +167,7 @@ newLeiosFetchContext leiosWriteLock leiosDb readLeiosEbBodies = do ----- leiosFetchHandler :: - ( - PrimMonad m - , - MonadMVar m - ) + IOLike m => LeiosFetchContext stmt m -> @@ -192,11 +185,7 @@ leiosFetchHandler leiosContext = LF.MkLeiosFetchRequestHandler $ \case pure $ LF.MsgLeiosBlockTxs x msgLeiosBlockRequest :: - ( - MonadMVar m - , - PrimMonad m - ) + IOLike m => LeiosFetchContext stmt m -> @@ -211,22 +200,17 @@ msgLeiosBlockRequest leiosContext p = do Just _ -> error "Unrecognized Leios point" n <- MVar.withMVar leiosWriteLock $ \() -> do -- get the EB items - dbExec db (fromString "BEGIN") - stmt <- dbPrepare db (fromString sql_lookup_ebBodies) - dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) - let loop !i = - dbStep db stmt >>= \case - DB.Done -> do - dbFinalize db stmt - pure i - DB.Row -> do - txHashBytes <- dbColumnBlob db stmt 0 - txBytesSize <- fromIntegral <$> dbColumnInt64 db stmt 1 - MV.write buf i (MkTxHash txHashBytes, txBytesSize) - loop (i+1) - n <- loop 0 - dbExec db (fromString "COMMIT") - pure n + dbWithBEGIN db $ dbWithPrepare db (fromString sql_lookup_ebBodies) $ \stmt -> do + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + let loop !i = + dbStep db stmt >>= \case + DB.Done -> pure i + DB.Row -> do + txHashBytes <- dbColumnBlob db stmt 0 + txBytesSize <- fromIntegral <$> dbColumnInt64 db stmt 1 + MV.write buf i (MkTxHash txHashBytes, txBytesSize) + loop (i+1) + loop 0 v <- V.freeze $ MV.slice 0 n buf pure $ MkLeiosEb v @@ -238,11 +222,7 @@ sql_lookup_ebBodies = \" msgLeiosBlockTxsRequest :: - ( - MonadMVar m - , - PrimMonad m - ) + IOLike m => LeiosFetchContext stmt m -> @@ -273,36 +253,30 @@ msgLeiosBlockTxsRequest leiosContext p bitmaps = do Just (i, bitmap') -> Just (64 * fromIntegral idx + i, (idx, bitmap') : k) txOffsets = unfoldr nextOffset bitmaps - n <- MVar.withMVar leiosWriteLock $ \() -> do + n <- MVar.withMVar leiosWriteLock $ \() -> dbWithBEGIN db $ do -- fill in-memory table - dbExec db (fromString "BEGIN") - do - stmt <- dbPrepare db (fromString sql_insert_memTxPoints) + dbWithPrepare db (fromString sql_insert_memTxPoints) $ \stmt -> do dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) forM_ txOffsets $ \txOffset -> do dbBindInt64 db stmt 2 (fromIntegral txOffset) dbStep1 db stmt dbReset db stmt - dbFinalize db stmt -- get txBytess - stmt <- dbPrepare db (fromString sql_retrieve_from_ebTxs) - n <- (\f -> foldM f 0 txOffsets) $ \i txOffset -> do - dbStep db stmt >>= \case - DB.Done -> do - dbFinalize db stmt - pure i - DB.Row -> do - txOffset' <- dbColumnInt64 db stmt 0 - txBytes <- dbColumnBlob db stmt 1 - when (fromIntegral txOffset /= txOffset') $ do - error $ "Missing offset " ++ show (txOffset, txOffset') - tx <- case decodeFullDecoder' (fromString "txBytes column") Leios.decodeLeiosTx txBytes of - Left err -> error $ "Failed to deserialize txBytes column: " ++ Leios.prettyLeiosPoint p ++ " " ++ show (txOffset', err) - Right tx -> pure tx - MV.write buf i tx - pure $! (i + 1) + n <- dbWithPrepare db (fromString sql_retrieve_from_ebTxs) $ \stmt -> do + (\f -> foldM f 0 txOffsets) $ \i txOffset -> do + dbStep db stmt >>= \case + DB.Done -> pure i + DB.Row -> do + txOffset' <- dbColumnInt64 db stmt 0 + txBytes <- dbColumnBlob db stmt 1 + when (fromIntegral txOffset /= txOffset') $ do + error $ "Missing offset " ++ show (txOffset, txOffset') + tx <- case decodeFullDecoder' (fromString "txBytes column") Leios.decodeLeiosTx txBytes of + Left err -> error $ "Failed to deserialize txBytes column: " ++ Leios.prettyLeiosPoint p ++ " " ++ show (txOffset', err) + Right tx -> pure tx + MV.write buf i tx + pure $! (i + 1) dbExec db (fromString sql_flush_memTxPoints) - dbExec db (fromString "COMMIT") pure n V.freeze $ MV.slice 0 n buf @@ -637,9 +611,7 @@ nextLeiosFetchClientCommand :: forall pid stmt m. ( Ord pid , - MonadSTM m - , - MonadMVar m + IOLike m ) => StrictSTM.STM m Bool @@ -696,9 +668,7 @@ msgLeiosBlock :: ( Ord pid , - MonadMVar m - , - MonadSTM m + IOLike m ) => (MVar m (), MVar m LeiosEbBodies, MVar m (LeiosOutstanding pid), MVar m (), MVar m (Map (PeerId pid) (StrictTVar m (Map SlotNo (Seq LeiosNotification))))) @@ -736,18 +706,15 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVar Nothing -> pure x let novel = not $ Set.member ebId (Leios.acquiredEbBodies ebBodies) when novel $ MVar.withMVar writeLock $ \() -> do -- TODO don't hold the ebBodies mvar during this IO - stmt <- dbPrepare db (fromString sql_insert_ebBody) - dbExec db (fromString "BEGIN") - -- INSERT INTO ebTxs - dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) - V.iforM_ (let MkLeiosEb v = eb in v) $ \txOffset (txHash, txBytesSize) -> do - dbBindInt64 db stmt 2 (fromIntegral txOffset) - dbBindBlob db stmt 3 (let MkTxHash bytes = txHash in bytes) - dbBindInt64 db stmt 4 (fromIntegral txBytesSize) - dbStep1 db stmt - dbReset db stmt - dbFinalize db stmt - dbExec db (fromString "COMMIT") + dbWithBEGIN db $ dbWithPrepare db (fromString sql_insert_ebBody) $ \stmt -> do + -- INSERT INTO ebTxs + dbBindInt64 db stmt 1 (Leios.fromIntegralEbId ebId) + V.iforM_ (let MkLeiosEb v = eb in v) $ \txOffset (txHash, txBytesSize) -> do + dbBindInt64 db stmt 2 (fromIntegral txOffset) + dbBindBlob db stmt 3 (let MkTxHash bytes = txHash in bytes) + dbBindInt64 db stmt 4 (fromIntegral txBytesSize) + dbStep1 db stmt + dbReset db stmt -- update NodeKernel state let !ebBodies' = if not novel then ebBodies else ebBodies { Leios.acquiredEbBodies = Set.insert ebId (Leios.acquiredEbBodies ebBodies) @@ -831,9 +798,7 @@ msgLeiosBlockTxs :: ( Ord pid , - MonadMVar m - , - MonadSTM m + IOLike m ) => ( @@ -892,24 +857,21 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notification offsets = unfoldr nextOffset bitmaps -- ingest MVar.withMVar writeLock $ \() -> do - stmtTxCache <- dbPrepare db (fromString sql_insert_txCache) - stmtEbTxs <- dbPrepare db (fromString sql_update_ebTx) - dbBindInt64 db stmtEbTxs 2 (Leios.fromIntegralEbId ebId) - dbExec db (fromString "BEGIN") - forM_ (zip offsets $ V.toList $ txHashes `V.zip` txBytess) $ \(txOffset, (txHash, txBytes)) -> do - -- INTO ebTxs - dbBindInt64 db stmtEbTxs 3 $ fromIntegral txOffset - dbBindBlob db stmtEbTxs 1 $ txBytes - dbStep1 db stmtEbTxs - dbReset db stmtEbTxs - -- INTO txCache - dbBindBlob db stmtTxCache 1 $ (let MkTxHash bytes = txHash in bytes) - dbBindBlob db stmtTxCache 2 $ txBytes - dbBindInt64 db stmtTxCache 3 $ fromIntegral $ BS.length txBytes - dbStep1 db stmtTxCache - dbReset db stmtTxCache - dbExec db (fromString "COMMIT") - -- update NodeKernel state + dbWithBEGIN db $ dbWithPrepare db (fromString sql_insert_txCache) $ \stmtTxCache -> dbWithPrepare db (fromString sql_update_ebTx) $ \stmtEbTxs -> do + dbBindInt64 db stmtEbTxs 2 (Leios.fromIntegralEbId ebId) + forM_ (zip offsets $ V.toList $ txHashes `V.zip` txBytess) $ \(txOffset, (txHash, txBytes)) -> do + -- INTO ebTxs + dbBindInt64 db stmtEbTxs 3 $ fromIntegral txOffset + dbBindBlob db stmtEbTxs 1 $ txBytes + dbStep1 db stmtEbTxs + dbReset db stmtEbTxs + -- INTO txCache + dbBindBlob db stmtTxCache 1 $ (let MkTxHash bytes = txHash in bytes) + dbBindBlob db stmtTxCache 2 $ txBytes + dbBindInt64 db stmtTxCache 3 $ fromIntegral $ BS.length txBytes + dbStep1 db stmtTxCache + dbReset db stmtTxCache + -- update NodeKernel state newNotifications <- MVar.modifyMVar outstandingVar $ \outstanding -> do let (requestedTxPeers', cachedTxs', txOffsetss', txsBytesSize) = (\f -> V.foldl @@ -1036,11 +998,7 @@ sql_insert_txCache = ----- doCacheCopy :: - ( - MonadMVar m - , - MonadSTM m - ) + IOLike m => LeiosDb stmt m -> @@ -1059,12 +1017,8 @@ doCacheCopy db (writeLock, outstandingVar, notificationVars) bytesSize = do copied <- do outstanding <- MVar.readMVar outstandingVar MVar.withMVar writeLock $ \() -> do - dbExec db (fromString "BEGIN") - stmt <- dbPrepare db (fromString sql_copy_from_txCache) - x <- go1 stmt Map.empty 0 (Leios.toCopy outstanding) - dbFinalize db stmt - dbExec db (fromString "COMMIT") - pure x + dbWithBEGIN db $ dbWithPrepare db (fromString sql_copy_from_txCache) $ \stmt -> do + go1 stmt Map.empty 0 (Leios.toCopy outstanding) (moreTodo, newNotifications) <- MVar.modifyMVar outstandingVar $ \outstanding -> do let _ = copied :: Map EbId IntSet let usefulCopied = diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 0ba90a7d3d..aefa170fd5 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -16,6 +16,7 @@ import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM +import Control.Monad.Class.MonadThrow (MonadThrow, bracket, bracket_) import Data.ByteString (ByteString) import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Char8 as BS8 @@ -417,6 +418,22 @@ dbFinalize = dbFinalize_ dbPrepare :: HasCallStack => LeiosDb stmt m -> DB.Utf8 -> m stmt dbPrepare = dbPrepare_ +dbWithPrepare :: + (HasCallStack, MonadThrow m) + => + LeiosDb stmt m -> DB.Utf8 -> (stmt -> m r) -> m r +dbWithPrepare db q k = bracket (dbPrepare db q) (dbFinalize db) k + +dbWithBEGIN :: + (HasCallStack, MonadThrow m) + => + LeiosDb stmt m -> m r -> m r +dbWithBEGIN db k = do + bracket_ + (dbExec db (fromString "BEGIN")) + (dbExec db (fromString "COMMIT")) + k + dbReset :: HasCallStack => LeiosDb stmt m -> stmt -> m () dbReset = dbReset_ @@ -474,7 +491,7 @@ withDieDone io = DB.Done -> pure () dieStack :: HasCallStack => String -> IO a -dieStack s = dieStack $ s ++ "\n\n" ++ GHC.Stack.prettyCallStack GHC.Stack.callStack +dieStack s = die $ s ++ "\n\n" ++ GHC.Stack.prettyCallStack GHC.Stack.callStack ----- From 19f570722834b5d082d1aebfc225505e1b4d59f5 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Mon, 27 Oct 2025 20:22:12 -0700 Subject: [PATCH 108/119] leiosdemo202510: LeiosFetch for downstream too --- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index aefa170fd5..9630ac0c1c 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -16,7 +16,8 @@ import Control.Concurrent.Class.MonadMVar (MVar) import qualified Control.Concurrent.Class.MonadMVar as MVar import Control.Concurrent.Class.MonadSTM.Strict (StrictTVar) import qualified Control.Concurrent.Class.MonadSTM.Strict as StrictSTM -import Control.Monad.Class.MonadThrow (MonadThrow, bracket, bracket_) +import Control.Monad.Class.MonadThrow (MonadThrow, bracket, generalBracket) +import qualified Control.Monad.Class.MonadThrow as MonadThrow import Data.ByteString (ByteString) import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString.Char8 as BS8 @@ -425,14 +426,19 @@ dbWithPrepare :: dbWithPrepare db q k = bracket (dbPrepare db q) (dbFinalize db) k dbWithBEGIN :: - (HasCallStack, MonadThrow m) + (HasCallStack, IOLike m) => LeiosDb stmt m -> m r -> m r dbWithBEGIN db k = do - bracket_ + fmap fst + $ generalBracket (dbExec db (fromString "BEGIN")) - (dbExec db (fromString "COMMIT")) - k + (\() -> \case + MonadThrow.ExitCaseSuccess _ -> dbExec db (fromString "COMMIT") + MonadThrow.ExitCaseException _ -> dbExec db (fromString "ROLLBACK") + MonadThrow.ExitCaseAbort -> dbExec db (fromString "ROLLBACK") + ) + (\() -> k) dbReset :: HasCallStack => LeiosDb stmt m -> stmt -> m () dbReset = dbReset_ From ea74e1b398a3739d00fda4a8869c078372348381 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 07:16:27 -0700 Subject: [PATCH 109/119] leiosdemo202510: add a 2nd node-under-test, but not seeing mixed traffic? --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 5 +- .../Ouroboros/Consensus/Node.hs | 1 + .../src/ouroboros-consensus/LeiosDemoLogic.hs | 14 +++- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 2 +- scripts/leios-demo/leios-october-demo.sh | 81 +++++++++++++++---- 5 files changed, 81 insertions(+), 22 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index a39e214688..4449d757a6 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -253,6 +253,7 @@ mkHandlers :: , LedgerSupportsProtocol blk , Ord addrNTN , Hashable addrNTN + , Show addrNTN ) => NodeKernelArgs m addrNTN addrNTC blk -> NodeKernel m addrNTN addrNTC blk @@ -318,7 +319,7 @@ mkHandlers (pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do - traceM $ "MsgLeiosBlockOffer " <> Leios.prettyLeiosPoint p + traceM $ "MsgLeiosBlockOffer " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peer ++ ")" ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do let (ebId, mbEbBodies2) = Leios.ebIdFromPoint p ebBodies1 ebBodies2 = fromMaybe ebBodies1 mbEbBodies2 @@ -340,7 +341,7 @@ mkHandlers pure (offers1', offers2) void $ MVar.tryPutMVar getLeiosReady () MsgLeiosBlockTxsOffer p -> do - traceM $ "MsgLeiosBlockTxsOffer " <> Leios.prettyLeiosPoint p + traceM $ "MsgLeiosBlockTxsOffer " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peer ++ ")" ebId <- Leios.ebIdFromPointM getLeiosEbBodies p peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs index e52521fcba..61798ee142 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs @@ -481,6 +481,7 @@ runWith :: forall m addrNTN addrNTC blk p2p. , Hashable addrNTN -- the constraint comes from `initNodeKernel` , NetworkIO m , NetworkAddr addrNTN + , Show addrNTN ) => RunNodeArgs m addrNTN addrNTC blk p2p -> (NodeToNodeVersion -> addrNTN -> CBOR.Encoding) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index c10fa37455..1c102e6e71 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -610,6 +610,8 @@ packRequests env ebBodies = nextLeiosFetchClientCommand :: forall pid stmt m. ( Ord pid + , + Show pid , IOLike m ) @@ -666,6 +668,8 @@ nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do msgLeiosBlock :: ( + Show pid + , Ord pid , IOLike m @@ -685,7 +689,7 @@ msgLeiosBlock :: msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req eb = do -- validate it let MkLeiosBlockRequest p ebBytesSize = req - traceM $ "[start] MsgLeiosBlock " <> Leios.prettyLeiosPoint p + traceM $ "[start] MsgLeiosBlock " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peerId ++ ")" do let MkLeiosPoint _ebSlot ebHash = p let ebBytes :: ByteString @@ -780,7 +784,7 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVar (Seq.singleton (LeiosOfferBlock ebId ebBytesSize)) x StrictSTM.writeTVar var x' - traceM $ "[done] MsgLeiosBlock " <> Leios.prettyLeiosPoint p + traceM $ "[done] MsgLeiosBlock " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peerId ++ ")" sql_insert_ebBody :: String sql_insert_ebBody = @@ -797,6 +801,8 @@ delIf predicate x = if predicate x then Nothing else Just x msgLeiosBlockTxs :: ( Ord pid + , + Show pid , IOLike m ) @@ -823,7 +829,7 @@ msgLeiosBlockTxs :: -> m () msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req txs = do - traceM $ "[start] " ++ Leios.prettyLeiosBlockTxsRequest req + traceM $ "[start] " ++ Leios.prettyLeiosBlockTxsRequest req ++ " (from peer " ++ show peerId ++ ")" -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req -- forM_ txHashes $ \txHash -> do @@ -981,7 +987,7 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notification x <- StrictSTM.readTVar var let !x' = Map.unionWith (<>) x notifications StrictSTM.writeTVar var x' - traceM $ "[done] " ++ Leios.prettyLeiosBlockTxsRequest req + traceM $ "[done] " ++ Leios.prettyLeiosBlockTxsRequest req ++ " (from peer " ++ show peerId ++ ")" sql_update_ebTx :: String sql_update_ebTx = diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 9630ac0c1c..4c3b672ddc 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -55,7 +55,7 @@ fromIntegralEbId :: Integral a => EbId -> a fromIntegralEbId (MkEbId x) = fromIntegral x newtype PeerId a = MkPeerId a - deriving (Eq, Ord) + deriving (Eq, Ord, Show) newtype EbHash = MkEbHash ByteString deriving (Eq, Ord, Show) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 0af4e4c249..5ef5ae9f9a 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -40,11 +40,12 @@ fi # arbitrary choices -PORT1=3001 +PORT_UP=3001 PORT2=3002 PORT3=3003 +PORT4=3004 -echo "Ports: ${PORT1} ${PORT2} ${PORT3}" +echo "Ports: ${PORT_UP} ${PORT2} ${PORT3} ${PORT4}" TMP_DIR=$(mktemp -d ${TMPDIR:-/tmp}/leios-october-demo.XXXXXX) echo "Using temporary directory for DB and logs: $TMP_DIR" @@ -67,7 +68,7 @@ cat << EOF > topology-node-0.json "accessPoints": [ { "address": "127.0.0.1", - "port": ${PORT1} + "port": ${PORT_UP} } ], "advertise": false, @@ -82,7 +83,7 @@ EOF mkdir -p "$TMP_DIR/node-0/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-0/leios.db" -sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' +sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ ${CARDANO_NODE} run \ @@ -101,9 +102,10 @@ CARDANO_NODE_0_PID=$! echo "Cardano node 0 started with PID: $CARDANO_NODE_0_PID" ## -## Run a second Cardano-node (To be eventually replaced by a mocked downstream node) +## Run a second cardano-node (node-0) ## +echo "Creating topology-node-1.json in $(pwd)" cat << EOF > topology-node-1.json { "bootstrapPeers": [], @@ -112,7 +114,7 @@ cat << EOF > topology-node-1.json "accessPoints": [ { "address": "127.0.0.1", - "port": ${PORT2} + "port": ${PORT_UP} } ], "advertise": false, @@ -127,9 +129,9 @@ EOF mkdir -p "$TMP_DIR/node-1/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-1/leios.db" -sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' +sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM' -MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ +CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ ${CARDANO_NODE} run \ --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-1.json \ @@ -137,13 +139,62 @@ MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ --socket-path node-1.socket \ --host-addr 127.0.0.1 --port ${PORT3}" -echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" +echo "Command (Node 0): $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-1.log &" + +$CARDANO_NODE_CMD &> "$TMP_DIR/cardano-node-1.log" & + +CARDANO_NODE_1_PID=$! + +echo "Cardano node 1 started with PID: $CARDANO_NODE_1_PID" + +## +## Run a third Cardano-node (To be eventually replaced by a mocked downstream node) +## + +cat << EOF > topology-node-2.json +{ + "bootstrapPeers": [], + "localRoots": [ + { + "accessPoints": [ + { + "address": "127.0.0.1", + "port": ${PORT2} + }, + { + "address": "127.0.0.1", + "port": ${PORT3} + } + ], + "advertise": false, + "trustable": true, + "valency": 2 + } + ], + "publicRoots": [] +} +EOF + +mkdir -p "$TMP_DIR/node-2/db" + +cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-2/leios.db" +sqlite3 "$TMP_DIR/node-2/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' + +MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-2/leios.db \ + ${CARDANO_NODE} run \ + --config $CLUSTER_RUN_DATA/leios-node/config.json \ + --topology topology-node-2.json \ + --database-path $TMP_DIR/node-2/db \ + --socket-path node-2.socket \ + --host-addr 127.0.0.1 --port ${PORT4}" + +echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-2.log &" -$MOCKED_PEER_CMD &> "$TMP_DIR/cardano-node-1.log" & +$MOCKED_PEER_CMD &> "$TMP_DIR/cardano-node-2.log" & MOCKED_PEER_PID=$! -echo "Cardano node 1 started with PID: $MOCKED_PEER_PID" +echo "Mocked downstream peer started with PID: $MOCKED_PEER_PID" # Return to the original directory popd > /dev/null @@ -161,7 +212,7 @@ IMMDB_CMD_CORE="${IMMDB_SERVER} \ --initial-time $ONSET_OF_REF_SLOT --leios-schedule $LEIOS_SCHEDULE --leios-db $LEIOS_UPSTREAM_DB_PATH - --port ${PORT1}" + --port ${PORT_UP}" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -174,12 +225,12 @@ echo "ImmDB server started with PID: $IMMDB_SERVER_PID" read -n 1 -s -r -p "Press any key to stop the spawned processes..." echo -echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." +echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), $CARDANO_NODE_1_PID (node-1), and $MOCKED_PEER_PID (node-2)..." kill "$IMMDB_SERVER_PID" 2>/dev/null || true -# Use negative PID to target the process group ID and SIGKILL for cardano-node processes. kill "$CARDANO_NODE_0_PID" 2>/dev/null || true +kill "$CARDANO_NODE_1_PID" 2>/dev/null || true kill "$MOCKED_PEER_PID" 2>/dev/null || true @@ -200,7 +251,7 @@ echo "Temporary data stored at: $TMP_DIR" # python3 scripts/leios-demo/log_parser.py \ # $REF_SLOT $ONSET_OF_REF_SLOT \ -# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ +# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-2.log \ # "scatter_plot.png" # # 2. Deactivate the Python Virtual Environment before exiting From 903890c8cb6e16540e256a020ebb8fbd962f188a Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 07:16:29 -0700 Subject: [PATCH 110/119] Revert "leiosdemo202510: add a 2nd node-under-test, but not seeing mixed traffic?" This reverts commit ea74e1b398a3739d00fda4a8869c078372348381. --- .../Ouroboros/Consensus/Network/NodeToNode.hs | 5 +- .../Ouroboros/Consensus/Node.hs | 1 - .../src/ouroboros-consensus/LeiosDemoLogic.hs | 14 +--- .../src/ouroboros-consensus/LeiosDemoTypes.hs | 2 +- scripts/leios-demo/leios-october-demo.sh | 81 ++++--------------- 5 files changed, 22 insertions(+), 81 deletions(-) diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs index 4449d757a6..a39e214688 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Network/NodeToNode.hs @@ -253,7 +253,6 @@ mkHandlers :: , LedgerSupportsProtocol blk , Ord addrNTN , Hashable addrNTN - , Show addrNTN ) => NodeKernelArgs m addrNTN addrNTC blk -> NodeKernel m addrNTN addrNTC blk @@ -319,7 +318,7 @@ mkHandlers (pure $ \case MsgLeiosBlockAnnouncement{} -> error "Demo does not send EB announcements!" MsgLeiosBlockOffer p ebBytesSize -> do - traceM $ "MsgLeiosBlockOffer " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peer ++ ")" + traceM $ "MsgLeiosBlockOffer " <> Leios.prettyLeiosPoint p ebId <- MVar.modifyMVar getLeiosEbBodies $ \ebBodies1 -> do let (ebId, mbEbBodies2) = Leios.ebIdFromPoint p ebBodies1 ebBodies2 = fromMaybe ebBodies1 mbEbBodies2 @@ -341,7 +340,7 @@ mkHandlers pure (offers1', offers2) void $ MVar.tryPutMVar getLeiosReady () MsgLeiosBlockTxsOffer p -> do - traceM $ "MsgLeiosBlockTxsOffer " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peer ++ ")" + traceM $ "MsgLeiosBlockTxsOffer " <> Leios.prettyLeiosPoint p ebId <- Leios.ebIdFromPointM getLeiosEbBodies p peerVars <- do peersVars <- MVar.readMVar getLeiosPeersVars diff --git a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs index 61798ee142..e52521fcba 100644 --- a/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs +++ b/ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs @@ -481,7 +481,6 @@ runWith :: forall m addrNTN addrNTC blk p2p. , Hashable addrNTN -- the constraint comes from `initNodeKernel` , NetworkIO m , NetworkAddr addrNTN - , Show addrNTN ) => RunNodeArgs m addrNTN addrNTC blk p2p -> (NodeToNodeVersion -> addrNTN -> CBOR.Encoding) diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs index 1c102e6e71..c10fa37455 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoLogic.hs @@ -610,8 +610,6 @@ packRequests env ebBodies = nextLeiosFetchClientCommand :: forall pid stmt m. ( Ord pid - , - Show pid , IOLike m ) @@ -668,8 +666,6 @@ nextLeiosFetchClientCommand stopSTM kernelVars db peerId reqsVar = do msgLeiosBlock :: ( - Show pid - , Ord pid , IOLike m @@ -689,7 +685,7 @@ msgLeiosBlock :: msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req eb = do -- validate it let MkLeiosBlockRequest p ebBytesSize = req - traceM $ "[start] MsgLeiosBlock " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peerId ++ ")" + traceM $ "[start] MsgLeiosBlock " <> Leios.prettyLeiosPoint p do let MkLeiosPoint _ebSlot ebHash = p let ebBytes :: ByteString @@ -784,7 +780,7 @@ msgLeiosBlock (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVar (Seq.singleton (LeiosOfferBlock ebId ebBytesSize)) x StrictSTM.writeTVar var x' - traceM $ "[done] MsgLeiosBlock " ++ Leios.prettyLeiosPoint p ++ " (from peer " ++ show peerId ++ ")" + traceM $ "[done] MsgLeiosBlock " <> Leios.prettyLeiosPoint p sql_insert_ebBody :: String sql_insert_ebBody = @@ -801,8 +797,6 @@ delIf predicate x = if predicate x then Nothing else Just x msgLeiosBlockTxs :: ( Ord pid - , - Show pid , IOLike m ) @@ -829,7 +823,7 @@ msgLeiosBlockTxs :: -> m () msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notificationVars) db peerId req txs = do - traceM $ "[start] " ++ Leios.prettyLeiosBlockTxsRequest req ++ " (from peer " ++ show peerId ++ ")" + traceM $ "[start] " ++ Leios.prettyLeiosBlockTxsRequest req -- validate it let MkLeiosBlockTxsRequest p bitmaps txHashes = req -- forM_ txHashes $ \txHash -> do @@ -987,7 +981,7 @@ msgLeiosBlockTxs (writeLock, ebBodiesVar, outstandingVar, readyVar, notification x <- StrictSTM.readTVar var let !x' = Map.unionWith (<>) x notifications StrictSTM.writeTVar var x' - traceM $ "[done] " ++ Leios.prettyLeiosBlockTxsRequest req ++ " (from peer " ++ show peerId ++ ")" + traceM $ "[done] " ++ Leios.prettyLeiosBlockTxsRequest req sql_update_ebTx :: String sql_update_ebTx = diff --git a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs index 4c3b672ddc..9630ac0c1c 100644 --- a/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs +++ b/ouroboros-consensus/src/ouroboros-consensus/LeiosDemoTypes.hs @@ -55,7 +55,7 @@ fromIntegralEbId :: Integral a => EbId -> a fromIntegralEbId (MkEbId x) = fromIntegral x newtype PeerId a = MkPeerId a - deriving (Eq, Ord, Show) + deriving (Eq, Ord) newtype EbHash = MkEbHash ByteString deriving (Eq, Ord, Show) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 5ef5ae9f9a..0af4e4c249 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -40,12 +40,11 @@ fi # arbitrary choices -PORT_UP=3001 +PORT1=3001 PORT2=3002 PORT3=3003 -PORT4=3004 -echo "Ports: ${PORT_UP} ${PORT2} ${PORT3} ${PORT4}" +echo "Ports: ${PORT1} ${PORT2} ${PORT3}" TMP_DIR=$(mktemp -d ${TMPDIR:-/tmp}/leios-october-demo.XXXXXX) echo "Using temporary directory for DB and logs: $TMP_DIR" @@ -68,7 +67,7 @@ cat << EOF > topology-node-0.json "accessPoints": [ { "address": "127.0.0.1", - "port": ${PORT_UP} + "port": ${PORT1} } ], "advertise": false, @@ -83,7 +82,7 @@ EOF mkdir -p "$TMP_DIR/node-0/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-0/leios.db" -sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' +sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ ${CARDANO_NODE} run \ @@ -102,10 +101,9 @@ CARDANO_NODE_0_PID=$! echo "Cardano node 0 started with PID: $CARDANO_NODE_0_PID" ## -## Run a second cardano-node (node-0) +## Run a second Cardano-node (To be eventually replaced by a mocked downstream node) ## -echo "Creating topology-node-1.json in $(pwd)" cat << EOF > topology-node-1.json { "bootstrapPeers": [], @@ -114,7 +112,7 @@ cat << EOF > topology-node-1.json "accessPoints": [ { "address": "127.0.0.1", - "port": ${PORT_UP} + "port": ${PORT2} } ], "advertise": false, @@ -129,9 +127,9 @@ EOF mkdir -p "$TMP_DIR/node-1/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-1/leios.db" -sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM' +sqlite3 "$TMP_DIR/node-1/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' -CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ +MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ ${CARDANO_NODE} run \ --config $CLUSTER_RUN_DATA/leios-node/config.json \ --topology topology-node-1.json \ @@ -139,62 +137,13 @@ CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-1/leios.db \ --socket-path node-1.socket \ --host-addr 127.0.0.1 --port ${PORT3}" -echo "Command (Node 0): $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-1.log &" - -$CARDANO_NODE_CMD &> "$TMP_DIR/cardano-node-1.log" & - -CARDANO_NODE_1_PID=$! - -echo "Cardano node 1 started with PID: $CARDANO_NODE_1_PID" - -## -## Run a third Cardano-node (To be eventually replaced by a mocked downstream node) -## - -cat << EOF > topology-node-2.json -{ - "bootstrapPeers": [], - "localRoots": [ - { - "accessPoints": [ - { - "address": "127.0.0.1", - "port": ${PORT2} - }, - { - "address": "127.0.0.1", - "port": ${PORT3} - } - ], - "advertise": false, - "trustable": true, - "valency": 2 - } - ], - "publicRoots": [] -} -EOF - -mkdir -p "$TMP_DIR/node-2/db" - -cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-2/leios.db" -sqlite3 "$TMP_DIR/node-2/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM;' - -MOCKED_PEER_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-2/leios.db \ - ${CARDANO_NODE} run \ - --config $CLUSTER_RUN_DATA/leios-node/config.json \ - --topology topology-node-2.json \ - --database-path $TMP_DIR/node-2/db \ - --socket-path node-2.socket \ - --host-addr 127.0.0.1 --port ${PORT4}" - -echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-2.log &" +echo "Command (Node 1): $MOCKED_PEER_CMD &> $TMP_DIR/cardano-node-1.log &" -$MOCKED_PEER_CMD &> "$TMP_DIR/cardano-node-2.log" & +$MOCKED_PEER_CMD &> "$TMP_DIR/cardano-node-1.log" & MOCKED_PEER_PID=$! -echo "Mocked downstream peer started with PID: $MOCKED_PEER_PID" +echo "Cardano node 1 started with PID: $MOCKED_PEER_PID" # Return to the original directory popd > /dev/null @@ -212,7 +161,7 @@ IMMDB_CMD_CORE="${IMMDB_SERVER} \ --initial-time $ONSET_OF_REF_SLOT --leios-schedule $LEIOS_SCHEDULE --leios-db $LEIOS_UPSTREAM_DB_PATH - --port ${PORT_UP}" + --port ${PORT1}" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -225,12 +174,12 @@ echo "ImmDB server started with PID: $IMMDB_SERVER_PID" read -n 1 -s -r -p "Press any key to stop the spawned processes..." echo -echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), $CARDANO_NODE_1_PID (node-1), and $MOCKED_PEER_PID (node-2)..." +echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." kill "$IMMDB_SERVER_PID" 2>/dev/null || true +# Use negative PID to target the process group ID and SIGKILL for cardano-node processes. kill "$CARDANO_NODE_0_PID" 2>/dev/null || true -kill "$CARDANO_NODE_1_PID" 2>/dev/null || true kill "$MOCKED_PEER_PID" 2>/dev/null || true @@ -251,7 +200,7 @@ echo "Temporary data stored at: $TMP_DIR" # python3 scripts/leios-demo/log_parser.py \ # $REF_SLOT $ONSET_OF_REF_SLOT \ -# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-2.log \ +# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ # "scatter_plot.png" # # 2. Deactivate the Python Virtual Environment before exiting From 188675287a5fdd66d29fe05b94f316ea50fc8626 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 07:16:56 -0700 Subject: [PATCH 111/119] leiosdemo202510: add missing VACUUM --- scripts/leios-demo/leios-october-demo.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 0af4e4c249..d01984f8d7 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -82,7 +82,7 @@ EOF mkdir -p "$TMP_DIR/node-0/db" cp "$LEIOS_UPSTREAM_DB_PATH" "$TMP_DIR/node-0/leios.db" -sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints;' +sqlite3 "$TMP_DIR/node-0/leios.db" 'DELETE FROM ebTxs; DELETE FROM txCache; DELETE FROM ebPoints; VACUUM' CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ ${CARDANO_NODE} run \ From af08f6aa091b6a38222a01bb2bd16f5533b5afcb Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 08:00:35 -0700 Subject: [PATCH 112/119] leiosdemo202510: do not elide CompletedBlockFetch --- nix/leios-mvd/leios-node/config.json | 1 - 1 file changed, 1 deletion(-) diff --git a/nix/leios-mvd/leios-node/config.json b/nix/leios-mvd/leios-node/config.json index 8380aa5fb0..2664e94f46 100644 --- a/nix/leios-mvd/leios-node/config.json +++ b/nix/leios-mvd/leios-node/config.json @@ -47,7 +47,6 @@ "severity": "Debug" }, "BlockFetch.Client.CompletedBlockFetch": { - "maxFrequency": 2.0 }, "BlockFetch.Decision": { "severity": "Notice" From 1a50c3b0fa6684258814a6f8abd309770fd35eb2 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 08:01:08 -0700 Subject: [PATCH 113/119] leiosdemo202510: hack leios-october-script.sh and log_parser.py to show text latencies --- scripts/leios-demo/leios-october-demo.sh | 33 ++++++++++++------------ scripts/leios-demo/log_parser.py | 26 ++++++++++--------- 2 files changed, 30 insertions(+), 29 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index d01984f8d7..3e1eefd0f6 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -153,6 +153,10 @@ popd > /dev/null ## ONSET_OF_REF_SLOT=$(( $now + ${SECONDS_UNTIL_REF_SLOT} )) +echo "REF_SLOT=$REF_SLOT" +echo "ONSET_OF_REF_SLOT=$ONSET_OF_REF_SLOT" +echo "$REF_SLOT" >ref_slot +echo "$ONSET_OF_REF_SLOT" >onset_of_ref_slot IMMDB_CMD_CORE="${IMMDB_SERVER} \ --db $CLUSTER_RUN_DATA/immdb-node/immutable/ \ @@ -185,25 +189,20 @@ kill "$MOCKED_PEER_PID" 2>/dev/null || true echo "Temporary data stored at: $TMP_DIR" -# # Log analysis +# Log analysis -# VENV_PATH="./scripts/leios-demo/venv" +cat $TMP_DIR/cardano-node-0.log | grep -v -i -e leios >logA +cat $TMP_DIR/cardano-node-1.log | grep -v -i -e leios >logB -# # 1. Activate the Python Virtual Environment -# if [ -f "$VENV_PATH/bin/activate" ]; then -# echo "Activating virtual environment..." -# # 'source' must be used for activation to modify the current shell environment -# source "$VENV_PATH/bin/activate" -# else -# echo "Error: Virtual environment activation script not found at $VENV_PATH/bin/activate." >&2 -# fi +python3 ouroboros-consensus/scripts/leios-demo/log_parser.py \ + $REF_SLOT $ONSET_OF_REF_SLOT \ + logA logB \ + "scatter_plot.png" -# python3 scripts/leios-demo/log_parser.py \ -# $REF_SLOT $ONSET_OF_REF_SLOT \ -# $TMP_DIR/cardano-node-0.log $TMP_DIR/cardano-node-1.log \ -# "scatter_plot.png" +# Status -# # 2. Deactivate the Python Virtual Environment before exiting -# deactivate 2>/dev/null || true +echo +echo Any processes still running: +ps -aux | grep -e '[c]ardano-node' -e '[i]mmdb' | cut -c-180 -# exit 0 +exit 0 diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 20650c7045..8389038fca 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -328,11 +328,6 @@ def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): how="inner", ) - # --- STEP 5: Calculate Latency (Time Difference) --- - df_merged["latency_ms"] = ( - df_merged["at_node_1"] - df_merged["at_node_0"] - ).dt.total_seconds() * 1000 - # --- STEP 6: Calculate Slot Onset Time --- print(f"\n--- Calculating Slot Onset Times ---") print( @@ -359,6 +354,11 @@ def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): # Continue without onset time if calculation fails pass + # --- STEP 5: Calculate Latency (Time Difference) --- + df_merged["latency_ms"] = ( + df_merged["at_node_1"] - df_merged["slot_onset"] + ).dt.total_seconds() * 1000 + # --- STEP 7: Calculate Diffs from Previous Slot --- print("\n--- Calculating Diffs from Previous Slot ---") @@ -382,7 +382,7 @@ def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): # --- STEP 8: Generate Scatter Plot --- plot_onset_vs_arrival(df_merged, plot_output_file) - print("\n--- Extracted and Merged Data Summary (First 5 Rows) ---") + print("\n--- Extracted and Merged Data Summary ---") print( "Each row represents a unique block seen by both nodes, joined by hash and slot." ) @@ -390,17 +390,19 @@ def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): final_columns = [ "slot", "hash", - "slot_onset", - "at_node_0", - "at_node_1", +# "slot_onset", +# "at_node_0", +# "at_node_1", "latency_ms", - "slot_diff_from_prev", - "onset_diff_from_prev_s", +# "slot_diff_from_prev", +# "onset_diff_from_prev_s", ] # Filter list to only columns that actually exist in the dataframe # This prevents an error if 'slot_onset' failed to be created existing_columns = [col for col in final_columns if col in df_merged.columns] - print(df_merged[existing_columns].head()) + pd.set_option('display.max_columns', None) + pd.set_option('display.expand_frame_repr', False) + print(df_merged[existing_columns]) print(f"\nTotal unique block events matched: {len(df_merged)}") From 49026a688fb0a54475bdd0ce2d7ab179ba9ed59c Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 08:08:29 -0700 Subject: [PATCH 114/119] leiosdemo202510: disable scatter plot for now --- scripts/leios-demo/log_parser.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/scripts/leios-demo/log_parser.py b/scripts/leios-demo/log_parser.py index 8389038fca..0914fefa2c 100644 --- a/scripts/leios-demo/log_parser.py +++ b/scripts/leios-demo/log_parser.py @@ -380,7 +380,7 @@ def plot_onset_vs_arrival(df: pd.DataFrame, output_file: str = None): print("Warning: 'slot_onset' column not found. Skipping onset diff calculation.") # --- STEP 8: Generate Scatter Plot --- - plot_onset_vs_arrival(df_merged, plot_output_file) +# plot_onset_vs_arrival(df_merged, plot_output_file) print("\n--- Extracted and Merged Data Summary ---") print( From 17b42920229d7bc723a482e91f7fcfb21eecc6e5 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 08:20:02 -0700 Subject: [PATCH 115/119] leiosdemo202510: polishing the leios-october-script.sh --- scripts/leios-demo/leios-october-demo.sh | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 3e1eefd0f6..7aaa054502 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -1,7 +1,5 @@ #!/bin/bash -now=$(date +%s) - if [[ ! "$SECONDS_UNTIL_REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$SECONDS_UNTIL_REF_SLOT" -le 0 ]]; then echo "Error: \${SECONDS_UNTIL_REF_SLOT} must be a positive integer of seconds, which will be added to the execution time of this script." >&2 exit 1 @@ -38,6 +36,13 @@ if [[ -z "${REF_SLOT}" ]] || [[ ! "$REF_SLOT" =~ ^[0-9]*$ ]] || [[ "$REF_SLOT" - exit 1 fi +now=$(date +%s) +ONSET_OF_REF_SLOT=$(( $now + ${SECONDS_UNTIL_REF_SLOT} )) +echo "REF_SLOT=$REF_SLOT" +echo "ONSET_OF_REF_SLOT=$ONSET_OF_REF_SLOT" +echo "$REF_SLOT" >ref_slot +echo "$ONSET_OF_REF_SLOT" >onset_of_ref_slot + # arbitrary choices PORT1=3001 @@ -152,12 +157,6 @@ popd > /dev/null ## Run immdb-server ## -ONSET_OF_REF_SLOT=$(( $now + ${SECONDS_UNTIL_REF_SLOT} )) -echo "REF_SLOT=$REF_SLOT" -echo "ONSET_OF_REF_SLOT=$ONSET_OF_REF_SLOT" -echo "$REF_SLOT" >ref_slot -echo "$ONSET_OF_REF_SLOT" >onset_of_ref_slot - IMMDB_CMD_CORE="${IMMDB_SERVER} \ --db $CLUSTER_RUN_DATA/immdb-node/immutable/ \ --config $CLUSTER_RUN_DATA/immdb-node/config.json \ From c0d12b931ed6b45d27438b499c2a07581c6881bf Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 09:21:50 -0700 Subject: [PATCH 116/119] leiosdemo202510: add README-Leios-October-demo.md and demoManifest.json --- README-Leios-October-demo.md | 85 ++++++++++++++++++++++++++++++++++++ demoManifest.json | 22 ++++++++++ 2 files changed, 107 insertions(+) create mode 100644 README-Leios-October-demo.md create mode 100644 demoManifest.json diff --git a/README-Leios-October-demo.md b/README-Leios-October-demo.md new file mode 100644 index 0000000000..2bca30e5f5 --- /dev/null +++ b/README-Leios-October-demo.md @@ -0,0 +1,85 @@ +# How to run the Leios Octoboer demo + +See https://github.com/IntersectMBO/ouroboros-consensus/issues/1701 for context. + +## Prepare the shell environment + +- If your environment can successfully execute `cabal build exe:cardano-node` from this commit, then it can build this demo's exes. + ```` + $ git log -1 10.5.1 + commit ca1ec278070baf4481564a6ba7b4a5b9e3d9f366 (tag: 10.5.1, origin/release/10.5.1, nfrisby/leiosdemo2025-anchor) + Author: Jordan Millar + Date: Wed Jul 2 08:24:11 2025 -0400 + + Bump node version to 10.5.1 + ``` +- The Python script needs `pandas` and `matplotlib`. +- The bash script needs `ps` (which on a `nix-shell` might require the `procps` package for matching CLIB, eg), and `sqlite`, and so on. +- Set `CONSENSUS_BUILD_DIR` to the absolute path of a directory in which `cabal build exe:immdb-server` will succeed. +- Set `NODE_BUILD_DIR` to the absolute path of a directory in which `cabal build exe:cardano-node` will succeed. +- Set `CONSENSUS_REPO_DIR` to the absolute path of the `ouroboros-consensus` repo. + +- Checkout a patched version of the `cardano-node` repository, something like the following, eg. + +``` +6119c5cff0 - (HEAD -> nfrisby/leiosdemo2025, origin/nfrisby/leiosdemo2025) WIP add Leios demo Consensus s-r-p (25 hours ago) +``` + +- If you're using a `source-repository-package` stanza for the `cabal build exe:cardano-node` command in the `NODE_BUILD_DIR`, confirm that it identifies the `ouroboros-consensus` commit you want to use (eg the one you're reading this file in). + +## Build the exes + +``` +$ (cd $CONSENSUS_BUILD_DIR; cabal build exe:immdb-server exe:leiosdemo202510) +$ IMMDB_SERVER="$(cd $CONSENSUS_BUILD_DIR; cabal list-bin exe:immdb-server)" +$ DEMO_TOOL="$(cd $CONSENSUS_BUILD_DIR; cabal list-bin exe:leiosdemo202510)" +$ (cd $CONSENSUS_BUILD_DIR; cabal build exe:cardano-node) +$ CARDANO_NODE="$(cd $CONSENSUS_BUILD_DIR; cabal list-bin exe:cardano-node)" +``` + +## Prepare the input data files + +``` +$ (cd $CONSENSUS_BUILD_DIR; $DEMO_TOOL generate demoUpstream.db "${CONSENSUS_REPO_DIR}/demoManifest.json" demoBaseSchedule.json) +$ cp demoBaseSchedule.json demoSchedule.json +$ # You must now edit demoSchedule.json so that the first number in each array is 182.9 +$ echo '[]' >emptySchedule.json +$ # create the following symlinks +$ (cd $CONSENSUS_REPO_DIR; ls -l $(find nix/ -name genesis-*.json)) +lrwxrwxrwx 1 nfrisby nifr 30 Oct 24 16:27 nix/leios-mvd/immdb-node/genesis-alonzo.json -> ../genesis/genesis.alonzo.json +lrwxrwxrwx 1 nfrisby nifr 29 Oct 24 16:27 nix/leios-mvd/immdb-node/genesis-byron.json -> ../genesis/genesis.byron.json +lrwxrwxrwx 1 nfrisby nifr 30 Oct 24 16:27 nix/leios-mvd/immdb-node/genesis-conway.json -> ../genesis/genesis.conway.json +lrwxrwxrwx 1 nfrisby nifr 31 Oct 24 16:27 nix/leios-mvd/immdb-node/genesis-shelley.json -> ../genesis/genesis.shelley.json +lrwxrwxrwx 1 nfrisby nifr 30 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-alonzo.json -> ../genesis/genesis.alonzo.json +lrwxrwxrwx 1 nfrisby nifr 29 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-byron.json -> ../genesis/genesis.byron.json +lrwxrwxrwx 1 nfrisby nifr 30 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-conway.json -> ../genesis/genesis.conway.json +lrwxrwxrwx 1 nfrisby nifr 31 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-shelley.json -> ../genesis/genesis.shelley.json +``` + +## Run the scenario + +Run the scenario with `emptySchedule.json`, ie no Leios traffic. + +``` +$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/emptySchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=182 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh +$ # wait about ~20 seconds before stopping the execution by pressing any key +``` + +Run the scenario with `demoSchedule.json`. + +``` +$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/demoSchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=182 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh +$ # wait about ~20 seconds before stopping the execution by pressing any key +``` + +## Analysis + +Compare and contrast the cell that is in the column for `latency_ms` and the row for the Praos block in slot 183. + +**WARNING**. +Each execution consumes about 0.5 gigabytes of disk. +The script announces where (eg `Temporary data stored at: /run/user/1000/leios-october-demo.c5Wmxc`), so you can delete each run's data when necessary. + +**INFO**. +If you don't see any data in the 'Extracted and Merged Data Summary' table, then check the log files in the run's temporary directory. +This is where you might see messages about, eg, the missing `genesis-*.json` files, bad syntax in the `demoSchedule.json` file, etc. diff --git a/demoManifest.json b/demoManifest.json new file mode 100644 index 0000000000..20e96f2f2f --- /dev/null +++ b/demoManifest.json @@ -0,0 +1,22 @@ +[ + {"slotNo": 0, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 1, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 2, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 3, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 4, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 5, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 6, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 7, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 8, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } + , + {"slotNo": 9, "txRecipes": [ 15390, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384, 16384] } +] + From 07200593e3defd7796117b8172db312e41fddd13 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 11:18:54 -0700 Subject: [PATCH 117/119] leiosdemo202510: add some documentation to README-Leios-October-demo.md --- README-Leios-October-demo.md | 128 ++++++++++++++++++++++++++++++++++- 1 file changed, 127 insertions(+), 1 deletion(-) diff --git a/README-Leios-October-demo.md b/README-Leios-October-demo.md index 2bca30e5f5..b6fab2b480 100644 --- a/README-Leios-October-demo.md +++ b/README-Leios-October-demo.md @@ -1,4 +1,4 @@ -# How to run the Leios Octoboer demo +# How to run the Leios October demo See https://github.com/IntersectMBO/ouroboros-consensus/issues/1701 for context. @@ -83,3 +83,129 @@ The script announces where (eg `Temporary data stored at: /run/user/1000/leios-o **INFO**. If you don't see any data in the 'Extracted and Merged Data Summary' table, then check the log files in the run's temporary directory. This is where you might see messages about, eg, the missing `genesis-*.json` files, bad syntax in the `demoSchedule.json` file, etc. + +# Details about the demo components + +## The topology + +For this first iteration, the demo topology is a simple linear chain. + +```mermaid +flowchart TD + MockedUpstreamPeer --> Node0 --> MockedDownstreamPeer +``` + +**INFO**. +In this iteration of the demo, the mocked downstream peer (see section below) is simply another node, ie Node1. + +## The Praos traffic and Leios traffic + +In this iteration of the demo, the Praos data and traffic is very simple. + +- The Praos data is a simple chain provided by the Performance&Tracing team. +- The mocked upstream peer serves each Praos block when the mocked wall-clock reaches the onset of their slots. +- The Leios data is ten 12.5 megabyte EBs. + They use the minimal number of txs necessary in order to accumulate 12.5 megabytes in order to minimize the CPU&heap overhead of the patched-in Leios logic, since this iteration of trhe demo is primarily intended to focus on networking. +- The mocked upstream peer serves those EBs just prior to the onset of one of the Praos block's slot, akin to (relatively minor) ATK-LeiosProtocolBurst attack. + Thus, the patched nodes are under significant Leios load when that Praos block begins diffusing. + +## The demo tool + +The `cabal run exe:leiosdemo202510 -- generate ...` command generates a SQLite database with the following schema. + +``` +CREATE TABLE ebPoints ( + ebSlot INTEGER NOT NULL + , + ebHashBytes BLOB NOT NULL + , + ebId INTEGER NOT NULL + , + PRIMARY KEY (ebSlot, ebHashBytes) + ) WITHOUT ROWID; +CREATE TABLE ebTxs ( + ebId INTEGER NOT NULL -- foreign key ebPoints.ebId + , + txOffset INTEGER NOT NULL + , + txHashBytes BLOB NOT NULL -- raw bytes + , + txBytesSize INTEGER NOT NULL + , + txBytes BLOB -- valid CBOR + , + PRIMARY KEY (ebId, txOffset) + ) WITHOUT ROWID; +``` + +The contents of the generated database are determine by the given `manifest.json` file. +For now, see the `demoManifest.json` file for the primary schema: each "`txRecipe`" is simply the byte size of the transaction. + +The `generate` subcommand also generates a default `schedule.json`. +Each EB will have two array elements in the schedule. +The first number in an array element is a fractional slot, which determines when the mocked upstream peer will offer the payload. +The rest of the array element is `MsgLeiosBlockOffer` if the EB's byte size is listed or `MsgLeiosBlockTxsOffer` if `null` is listed. + +The secondary schema of the manifest allows for EBs to overlap (which isn't necessary for this demo, despite the pathced node fully supporting it). +Overlap is created by an alternative "`txRecipe`", an object `{"share": "XYZ", "startIncl": 90, "stopExcl": 105}` where `"nickname": "XYZ"` was included in a preceding _source_ EB recipe. +The `"startIncl`" and `"stopExcl"` are inclusive and exclusive indices into the source EB (aka a left-closed right-open interval); `"stopExcl"` is optional and defaults to the length of the source EB. +With this `"share"` syntax, it is possible for an EB to include the same tx multiple times. +That would not be a well-formed EB, but the prototype's behavior in response to such an EB is undefined---it's fine for the prototype to simply assume all the Leios EBs and txs in their closures are well-formed. +(TODO check for this one, since it's easy to check for---just in the patched node itself, or also in `generate`?) + +## The mocked upstream peer + +The mocked upstream peer is a patched variant of `immdb-server`. + +- It runs incomplete variant of LeiosNotify and LeiosFetch: just EBs and EB closures, nothing else (no EB announcements, no votes, no range requests). +- It serves the EBs present in the given `--leios-db`; it sends Leios notificaitons offering the data according to the given `--leios-schedule`. + See the demo tool section above for how to generate those files. + +## The patched node/node-under-test + +The patched node is a patched variant of `cardano-node`. +All of the material changes were made in the `ouroboros-consensus` repo; the `cardano-node` changes are merely for integration. + +- It runs the same incomplete variant of LeiosNotify and LeiosFetch as the mocked upstream peer. +- The Leios fetch request logic is a fully fledged first draft, with four primary shortcomings. + - It only handles EBs and EB closures, not votes and not range requests. + - It retains a number of heap objects in proportion with the number of txs in EBs it has acquired. + The real node---and so subsequent iterations of this prototype---must instead keep that data on disk. + This first draft was intended to do so, but we struggled to invent the fetch logic algorithm with the constraint that some of its state was on-disk; that's currently presumed to be possible, but has been deferred to a iteration of the prototype. + - It never discards any information. + The real node---and so subsequent iterations of this prototype---must instead discard EBs and EB closures once their old enough, unless they are needed for the immutable chain. + - Once it decides to fetch a set of txs from an upstream peer for the sake of some EB closure, it does not necessarily compose those into an optimal set of requests for that peer. + We had not identified the potential for an optimizing algorithm here until writing this first prototype, so it just does something straight-forward and naive for now (which might be sufficient even for the real-node---we'll have to investigate later). + +There are no other changes. +In particular, that means the `ouroboros-network` mux doesn't not deprioritize Leios traffic. +That change is an example of what this first prototype is intended to potentially demonstrate the need for. +There are many such changes, from small to large. +Some examples includes the following. + +- The prototype uses SQLite3 with entirely default settings. + Maybe Write-Ahead Log mode would be much preferable, etc. +- The prototype uses a mutex to completely isolate every SQLite3 invocation---that's probably excessive, but was useful for some debugging during initial development (see the Engineering Notes appendix) +- The prototype chooses several _magic numbers_ for resource utilization limits (eg max-bytes per reqeusted, max outsanding bytes per peer, fetch decision logic rate-limiting, txCache disk-bandwidth rate-limiting, etc). + These all ultimately need to be tuned for the intended behvaiors on `mainnet`. +- The prototype does not deduplicate the storage of EBs' closures when they share txs. + This decision makes the LeiosFetch server a trivial single-pass instead of a join. + However, it "wastes" disk space and disk bandwidth. + It's left to future work to decide whether that's a worthwhile trade-off. + +## The mocked downstream node + +For simplicity, this is simply another instance of the patched node. +In the future, it could be comparatively lightweight and moreover could replay an arbitrary schedule of downstream requests, dual to the mocked upstream peer's arbitrary schedule of upstream notifications. + +# Appendix: Engineering Notes + +This section summaries some lessons learned during the development of this prototype. + +- Hypothesis: A SQLite connection will continue to hold SQLite's internal EXCLUSIVE lock _even after the transaction is COMMITed_ when the write transaction involved a prepared statement that was accidentally not finalized. + That hypothesis was inferred from a painstaking debugging session, but I haven't not yet confirmed it in isolation. + The bugfix unsuprisingly amounted to using `bracket` for all prepare/finalize pairs and all BEGIN/COMMIT pairs; thankfully our DB patterns seem to accommodate such bracketing. +- The SQLite query plan optimizer might need more information in order to be reliable. + Therefore at least one join (the one that copies out of `txCache` for the EbTxs identified in an in-memory table) was replaced with application-level iteration. + It's not yet clear whether a one-time ANALYZE call might suffice, for example. + Even if it did, it's also not yet clear how much bandwidth usage/latency/jitter/etc might be reduced. From 660207be627067354fb80c7d029f0d00b522a903 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 11:45:48 -0700 Subject: [PATCH 118/119] leiosdemo202510: fix typos in README-Leios-October-demo.md --- README-Leios-October-demo.md | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/README-Leios-October-demo.md b/README-Leios-October-demo.md index b6fab2b480..c757751fe0 100644 --- a/README-Leios-October-demo.md +++ b/README-Leios-October-demo.md @@ -88,7 +88,7 @@ This is where you might see messages about, eg, the missing `genesis-*.json` fil ## The topology -For this first iteration, the demo topology is a simple linear chain. +For this first iteration, the demo topology is a simple linear graph. ```mermaid flowchart TD @@ -100,7 +100,7 @@ In this iteration of the demo, the mocked downstream peer (see section below) is ## The Praos traffic and Leios traffic -In this iteration of the demo, the Praos data and traffic is very simple. +In this iteration of the demo, the data and traffic is very simple. - The Praos data is a simple chain provided by the Performance&Tracing team. - The mocked upstream peer serves each Praos block when the mocked wall-clock reaches the onset of their slots. @@ -157,7 +157,7 @@ That would not be a well-formed EB, but the prototype's behavior in response to The mocked upstream peer is a patched variant of `immdb-server`. -- It runs incomplete variant of LeiosNotify and LeiosFetch: just EBs and EB closures, nothing else (no EB announcements, no votes, no range requests). +- It runs incomplete variants of LeiosNotify and LeiosFetch: just EBs and EB closures, nothing else (no EB announcements, no votes, no range requests). - It serves the EBs present in the given `--leios-db`; it sends Leios notificaitons offering the data according to the given `--leios-schedule`. See the demo tool section above for how to generate those files. @@ -166,15 +166,15 @@ The mocked upstream peer is a patched variant of `immdb-server`. The patched node is a patched variant of `cardano-node`. All of the material changes were made in the `ouroboros-consensus` repo; the `cardano-node` changes are merely for integration. -- It runs the same incomplete variant of LeiosNotify and LeiosFetch as the mocked upstream peer. -- The Leios fetch request logic is a fully fledged first draft, with four primary shortcomings. +- It runs the same incomplete variants of LeiosNotify and LeiosFetch as the mocked upstream peer. +- The Leios fetch request logic is a fully fledged first draft, with following primary shortcomings. - It only handles EBs and EB closures, not votes and not range requests. - It retains a number of heap objects in proportion with the number of txs in EBs it has acquired. The real node---and so subsequent iterations of this prototype---must instead keep that data on disk. - This first draft was intended to do so, but we struggled to invent the fetch logic algorithm with the constraint that some of its state was on-disk; that's currently presumed to be possible, but has been deferred to a iteration of the prototype. + This first draft was intended to do so, but we struggled to invent the fetch logic algorithm with the constraint that some of its state was on-disk; that's currently presumed to be possible, but has been deferred to a subsequent iteration of the prototype. - It never discards any information. - The real node---and so subsequent iterations of this prototype---must instead discard EBs and EB closures once their old enough, unless they are needed for the immutable chain. - - Once it decides to fetch a set of txs from an upstream peer for the sake of some EB closure, it does not necessarily compose those into an optimal set of requests for that peer. + The real node---and so subsequent iterations of this prototype---must instead discard EBs and EB closures once they're old enough, unless they are needed for the immutable chain. + - Once it decides to fetch a set of txs from an upstream peer for the sake of some EB closure(s), it does not necessarily compose those into an optimal set of requests for that peer. We had not identified the potential for an optimizing algorithm here until writing this first prototype, so it just does something straight-forward and naive for now (which might be sufficient even for the real-node---we'll have to investigate later). There are no other changes. @@ -184,9 +184,9 @@ There are many such changes, from small to large. Some examples includes the following. - The prototype uses SQLite3 with entirely default settings. - Maybe Write-Ahead Log mode would be much preferable, etc. + Maybe Write-Ahead Log mode would be much preferable, likely need to VACUUM at some point, and so on. - The prototype uses a mutex to completely isolate every SQLite3 invocation---that's probably excessive, but was useful for some debugging during initial development (see the Engineering Notes appendix) -- The prototype chooses several _magic numbers_ for resource utilization limits (eg max-bytes per reqeusted, max outsanding bytes per peer, fetch decision logic rate-limiting, txCache disk-bandwidth rate-limiting, etc). +- The prototype chooses several _magic numbers_ for resource utilization limits (eg max bytes per reqeust, max outsanding bytes per peer, fetch decision logic rate-limiting, txCache disk-bandwidth rate-limiting, etc). These all ultimately need to be tuned for the intended behvaiors on `mainnet`. - The prototype does not deduplicate the storage of EBs' closures when they share txs. This decision makes the LeiosFetch server a trivial single-pass instead of a join. @@ -200,7 +200,7 @@ In the future, it could be comparatively lightweight and moreover could replay a # Appendix: Engineering Notes -This section summaries some lessons learned during the development of this prototype. +This section summarizes some lessons learned during the development of this prototype. - Hypothesis: A SQLite connection will continue to hold SQLite's internal EXCLUSIVE lock _even after the transaction is COMMITed_ when the write transaction involved a prepared statement that was accidentally not finalized. That hypothesis was inferred from a painstaking debugging session, but I haven't not yet confirmed it in isolation. From 1dba9a7929e6a2fdd62c3c58c4e5a71a4ec5c408 Mon Sep 17 00:00:00 2001 From: Nicolas Frisby Date: Tue, 28 Oct 2025 14:05:21 -0700 Subject: [PATCH 119/119] leiosdemo202510: update now that the simplest first experiment is working --- README-Leios-October-demo.md | 17 ++++++++++---- scripts/leios-demo/leios-october-demo.sh | 30 ++++++++++++++++++++---- 2 files changed, 39 insertions(+), 8 deletions(-) diff --git a/README-Leios-October-demo.md b/README-Leios-October-demo.md index c757751fe0..c31e57288a 100644 --- a/README-Leios-October-demo.md +++ b/README-Leios-October-demo.md @@ -14,7 +14,7 @@ See https://github.com/IntersectMBO/ouroboros-consensus/issues/1701 for context. Bump node version to 10.5.1 ``` - The Python script needs `pandas` and `matplotlib`. -- The bash script needs `ps` (which on a `nix-shell` might require the `procps` package for matching CLIB, eg), and `sqlite`, and so on. +- The various commands and bash scripts below needs `toxiproxy`, `sqlite`, `ps` (which on a `nix-shell` might require the `procps` package for matching CLIB, eg), and so on. - Set `CONSENSUS_BUILD_DIR` to the absolute path of a directory in which `cabal build exe:immdb-server` will succeed. - Set `NODE_BUILD_DIR` to the absolute path of a directory in which `cabal build exe:cardano-node` will succeed. - Set `CONSENSUS_REPO_DIR` to the absolute path of the `ouroboros-consensus` repo. @@ -56,25 +56,34 @@ lrwxrwxrwx 1 nfrisby nifr 30 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-conwa lrwxrwxrwx 1 nfrisby nifr 31 Oct 24 16:27 nix/leios-mvd/leios-node/genesis-shelley.json -> ../genesis/genesis.shelley.json ``` +## Prepare to run scenarios + +Ensure a toxiproxy server is running. + +``` +$ toxiproxy-server 1>toxiproxy.log 2>&1 & +``` + ## Run the scenario Run the scenario with `emptySchedule.json`, ie no Leios traffic. ``` -$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/emptySchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=182 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh +$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/emptySchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=177 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh $ # wait about ~20 seconds before stopping the execution by pressing any key ``` Run the scenario with `demoSchedule.json`. ``` -$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/demoSchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=182 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh +$ LEIOS_UPSTREAM_DB_PATH="$(pwd)/demoUpstream.db" LEIOS_SCHEDULE="$(pwd)/demoSchedule.json" SECONDS_UNTIL_REF_SLOT=5 REF_SLOT=177 CLUSTER_RUN_DATA="${CONSENSUS_REPO_DIR}/nix/leios-mvd" CARDANO_NODE=$CARDANO_NODE IMMDB_SERVER=$IMMDB_SERVER ${CONSENSUS_REPO_DIR}/scripts/leios-demo/leios-october-demo.sh $ # wait about ~20 seconds before stopping the execution by pressing any key ``` ## Analysis -Compare and contrast the cell that is in the column for `latency_ms` and the row for the Praos block in slot 183. +Compare and contrast the `latency_ms` column for the rows with a slot that's after the reference slot 177. +The first few such ros (ie those within a couple seconds of the reference slot) seem to often also be disrupted, because the initial bulk syncing to catch up to the reference slot presumably leaves the node in a disrupted state for a short interval. **WARNING**. Each execution consumes about 0.5 gigabytes of disk. diff --git a/scripts/leios-demo/leios-october-demo.sh b/scripts/leios-demo/leios-october-demo.sh index 7aaa054502..9aaabb160c 100755 --- a/scripts/leios-demo/leios-october-demo.sh +++ b/scripts/leios-demo/leios-october-demo.sh @@ -49,7 +49,26 @@ PORT1=3001 PORT2=3002 PORT3=3003 -echo "Ports: ${PORT1} ${PORT2} ${PORT3}" +TOXIPROXY=100 + +cleanup_proxy() { + toxiproxy-cli delete mocked-upstream-peer-proxy + toxiproxy-cli delete node0-proxy +} + +trap cleanup_proxy EXIT INT TERM + +toxiproxy-cli create --listen 127.0.0.1:"$PORT1" --upstream 127.0.0.1:"$(($TOXIPROXY + $PORT1))" mocked-upstream-peer-proxy +toxiproxy-cli create --listen 127.0.0.1:"$PORT2" --upstream 127.0.0.1:"$(($TOXIPROXY + $PORT2))" node0-proxy + +for i in mocked-upstream-peer-proxy node0-proxy; do + # TODO magic numbers + toxiproxy-cli toxic add --type latency --attribute latency=150 --attribute jitter=30 $i # milliseconds + toxiproxy-cli toxic add --type bandwidth --attribute rate=2500 $i # kilobytes per second + # FYI, 125 kilobyte/s = 1 megabit/s, so EG 2500 kilobyte/s = 20 megabit/s +done + +echo "Ports: ${PORT1} ${PORT2} ${PORT3}, each plus ${TOXIPROXY} for toxiproxy" TMP_DIR=$(mktemp -d ${TMPDIR:-/tmp}/leios-october-demo.XXXXXX) echo "Using temporary directory for DB and logs: $TMP_DIR" @@ -95,7 +114,7 @@ CARDANO_NODE_CMD="env LEIOS_DB_PATH=$TMP_DIR/node-0/leios.db \ --topology topology-node-0.json \ --database-path $TMP_DIR/node-0/db \ --socket-path node-0.socket \ - --host-addr 127.0.0.1 --port ${PORT2}" + --host-addr 127.0.0.1 --port $(($TOXIPROXY + $PORT2))" echo "Command (Node 0): $CARDANO_NODE_CMD &> $TMP_DIR/cardano-node-0.log &" @@ -164,7 +183,7 @@ IMMDB_CMD_CORE="${IMMDB_SERVER} \ --initial-time $ONSET_OF_REF_SLOT --leios-schedule $LEIOS_SCHEDULE --leios-db $LEIOS_UPSTREAM_DB_PATH - --port ${PORT1}" + --port $(($TOXIPROXY + $PORT1))" echo "Command: $IMMDB_CMD_CORE &> $TMP_DIR/immdb-server.log &" @@ -174,7 +193,8 @@ IMMDB_SERVER_PID=$! echo "ImmDB server started with PID: $IMMDB_SERVER_PID" -read -n 1 -s -r -p "Press any key to stop the spawned processes..." +TIMEOUT=25 +read -t $TIMEOUT -n 1 -s -r -p "Press any key to stop the spawned processes, or just wait $TIMEOUT seconds..." echo echo "Killing processes $IMMDB_SERVER_PID (immdb-server), $CARDANO_NODE_0_PID (node-0), and $MOCKED_PEER_PID (node-1)..." @@ -204,4 +224,6 @@ echo echo Any processes still running: ps -aux | grep -e '[c]ardano-node' -e '[i]mmdb' | cut -c-180 +echo "(Hopefully there were none!)" + exit 0