1010{-# LANGUAGE NamedFieldPuns #-}
1111{-# LANGUAGE RankNTypes #-}
1212{-# LANGUAGE ScopedTypeVariables #-}
13- {-# LANGUAGE TupleSections #-}
1413{-# LANGUAGE TypeApplications #-}
1514{-# LANGUAGE TypeOperators #-}
1615
@@ -19,6 +18,7 @@ module Cardano.CLI.EraBased.Run.Query
1918 , runQueryKesPeriodInfoCmd
2019 , runQueryLeadershipScheduleCmd
2120 , runQueryLedgerStateCmd
21+ , runQueryLedgerPeerSnapshot
2222 , runQueryPoolStateCmd
2323 , runQueryProtocolParametersCmd
2424 , runQueryProtocolStateCmd
@@ -43,7 +43,7 @@ import qualified Cardano.Api as Api
4343import qualified Cardano.Api.Consensus as Consensus
4444import Cardano.Api.Ledger (StandardCrypto , strictMaybeToMaybe )
4545import qualified Cardano.Api.Ledger as L
46- import Cardano.Api.Network (Serialised (.. ))
46+ import Cardano.Api.Network (LedgerPeerSnapshot , Serialised (.. ))
4747import qualified Cardano.Api.Network as Consensus
4848import Cardano.Api.Shelley hiding (QueryInShelleyBasedEra (.. ))
4949
@@ -103,6 +103,7 @@ runQueryCmds = \case
103103 Cmd. QueryStakeDistributionCmd args -> runQueryStakeDistributionCmd args
104104 Cmd. QueryStakeAddressInfoCmd args -> runQueryStakeAddressInfoCmd args
105105 Cmd. QueryLedgerStateCmd args -> runQueryLedgerStateCmd args
106+ Cmd. QueryLedgerPeerSnapshotCmd args -> runQueryLedgerPeerSnapshot args
106107 Cmd. QueryStakeSnapshotCmd args -> runQueryStakeSnapshotCmd args
107108 Cmd. QueryProtocolStateCmd args -> runQueryProtocolStateCmd args
108109 Cmd. QueryUTxOCmd args -> runQueryUTxOCmd args
@@ -834,6 +835,41 @@ runQueryLedgerStateCmd
834835 & onLeft (left . QueryCmdAcquireFailure )
835836 & onLeft left
836837
838+ runQueryLedgerPeerSnapshot
839+ :: ()
840+ => Cmd. QueryLedgerPeerSnapshotCmdArgs
841+ -> ExceptT QueryCmdError IO ()
842+ runQueryLedgerPeerSnapshot
843+ Cmd. QueryLedgerPeerSnapshotCmdArgs
844+ { Cmd. commons =
845+ Cmd. QueryCommons
846+ { Cmd. nodeSocketPath
847+ , Cmd. consensusModeParams
848+ , Cmd. networkId
849+ , Cmd. target
850+ }
851+ , Cmd. outFile
852+ } = do
853+ let localNodeConnInfo = LocalNodeConnectInfo consensusModeParams networkId nodeSocketPath
854+
855+ join $
856+ lift
857+ ( executeLocalStateQueryExpr localNodeConnInfo target $ runExceptT $ do
858+ AnyCardanoEra era <-
859+ lift queryCurrentEra
860+ & onLeft (left . QueryCmdUnsupportedNtcVersion )
861+
862+ sbe <-
863+ requireShelleyBasedEra era
864+ & onNothing (left QueryCmdByronEra )
865+
866+ result <- easyRunQuery (queryLedgerPeerSnapshot sbe)
867+
868+ pure $ shelleyBasedEraConstraints sbe (writeLedgerPeerSnapshot outFile) result
869+ )
870+ & onLeft (left . QueryCmdAcquireFailure )
871+ & onLeft left
872+
837873runQueryProtocolStateCmd
838874 :: ()
839875 => Cmd. QueryProtocolStateCmdArgs
@@ -1040,6 +1076,23 @@ writeLedgerState mOutFile qState@(SerialisedDebugLedgerState serLedgerState) =
10401076 LBS. writeFile fpath $
10411077 unSerialised serLedgerState
10421078
1079+ -- | Writes JSON-encoded big ledger peer snapshot
1080+ writeLedgerPeerSnapshot
1081+ :: Maybe (File () Out )
1082+ -> Serialised LedgerPeerSnapshot
1083+ -> ExceptT QueryCmdError IO ()
1084+ writeLedgerPeerSnapshot mOutPath serBigLedgerPeerSnapshot = do
1085+ case decodeBigLedgerPeerSnapshot serBigLedgerPeerSnapshot of
1086+ Left (bs, _decoderError) ->
1087+ firstExceptT QueryCmdHelpersError $ pPrintCBOR bs
1088+ Right snapshot ->
1089+ case mOutPath of
1090+ Nothing -> liftIO . LBS. putStrLn $ Aeson. encode snapshot
1091+ Just fpath ->
1092+ firstExceptT QueryCmdWriteFileError $
1093+ newExceptT . writeLazyByteStringFile fpath $
1094+ encodePretty snapshot
1095+
10431096writeStakeSnapshots
10441097 :: forall era ledgerera
10451098 . ()
0 commit comments