Skip to content

Commit 75f995b

Browse files
committed
WIP
1 parent 7f6ff14 commit 75f995b

File tree

4 files changed

+43
-22
lines changed

4 files changed

+43
-22
lines changed

ouroboros-consensus-cardano/app/snapshot-converter.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -311,23 +311,23 @@ main = withStdTerminalHandles $ do
311311
run conf args = do
312312
ccfg <- configCodec . pInfoConfig <$> mkProtocolInfo args
313313
let
314-
getState :: SomeHasFS IO -> FsPath -> IO (ExtLedgerState (CardanoBlock StandardCrypto) EmptyMK, CRC)
314+
getState :: SomeHasFS IO -> FsPath -> IO (LedgerState (CardanoBlock StandardCrypto) EmptyMK, CRC)
315315
getState fs path = do
316316
either
317317
(throwIO . SnapshotError . InitFailureRead @(CardanoBlock StandardCrypto) . ReadSnapshotFailed)
318-
pure
318+
(pure . first ledgerState)
319319
=<< runExceptT (readExtLedgerState fs (decodeDiskExtLedgerState ccfg) decode path)
320320

321321
(st, f) <- case from conf of
322322
Mem fp@(pathToDiskSnapshot -> Just (fs, path, _)) -> do
323-
-- (st, _) <- getState fs path
324-
pure (lstate, fromInMemory fp)
323+
(st, _) <- getState fs path
324+
pure (st, fromInMemory fp)
325325
LMDB fp@(pathToDiskSnapshot -> Just (fs, path, _)) -> do
326-
-- (st, _) <- getState (Debug.trace (show fp) fs) (Debug.traceShowId path </> mkFsPath ["state"])
327-
pure (lstate, fromLMDB (fp <> "/tables"))
328-
LSM fp@(pathToDiskSnapshot -> Just (fs, path, _)) fp2 -> do
329-
-- (st, _) <- getState fs path
330-
pure (lstate, fromLSM fp2)
326+
(st, _) <- getState (Debug.trace (show fp) fs) (Debug.traceShowId path </> mkFsPath ["state"])
327+
pure (st, fromLMDB (fp <> "/tables"))
328+
LSM fp@(pathToDiskSnapshot -> Just (fs, path, ds)) fp2 -> do
329+
(st, _) <- getState fs (Debug.traceShowId path </> mkFsPath ["state"])
330+
pure (st, fromLSM fp2 (dsSuffix ds))
331331
let t = case to conf of
332332
Mem fp@(pathToDiskSnapshot -> Just (fs, path, _)) ->
333333
toInMemory fp

ouroboros-consensus-cardano/src/ouroboros-consensus-cardano/Ouroboros/Consensus/Cardano/StreamingLedgerTables.hs

Lines changed: 12 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ import Cardano.Slotting.Time
2929
import qualified Codec.CBOR.Encoding
3030
import Control.ResourceRegistry
3131
import Control.Tracer (nullTracer)
32+
import qualified Data.Foldable as F
3233
import Data.Proxy
3334
import Data.SOP.BasicFunctors
3435
import Data.SOP.Functors
@@ -143,26 +144,30 @@ limits =
143144

144145
fromLSM ::
145146
FilePath ->
147+
Maybe String ->
146148
L EmptyMK ->
147149
ResourceRegistry IO ->
148150
IO (YieldArgs L IO)
149-
fromLSM fp hint reg = do
151+
fromLSM fp mSuffix hint reg = do
150152
(_, SomeHasFSAndBlockIO hasFS blockIO) <- stdMkBlockIOFS fp reg
151153
salt <- fst . genWord64 <$> newStdGen
152154
(_, session) <-
153155
allocate reg (\_ -> openSession nullTracer hasFS blockIO salt (mkFsPath ["lsm"])) closeSession
154156
tb <-
155157
allocate
156158
reg
157-
( \_ ->
159+
( \_ -> do
160+
F.traverse_ print =<< listSnapshots session
158161
openTableFromSnapshot
159162
session
160163
( toSnapshotName $
161-
show $
162-
unSlotNo $
163-
withOrigin (error "impossible") id $
164-
pointSlot $
165-
Ouroboros.Consensus.Ledger.Abstract.getTip hint
164+
maybe id (\su sl -> sl <> "_" <> su) mSuffix $
165+
( show $
166+
unSlotNo $
167+
withOrigin (error "impossible") id $
168+
pointSlot $
169+
Ouroboros.Consensus.Ledger.Abstract.getTip hint
170+
)
166171
)
167172
(SnapshotLabel $ T.pack "UTxO table")
168173
)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/LedgerDB/V2/LSM.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ module Ouroboros.Consensus.Storage.LedgerDB.V2.LSM
4747
, LSM.SnapshotLabel (LSM.SnapshotLabel)
4848
, LSM.openTableFromSnapshot
4949
, LSM.closeTable
50+
, LSM.listSnapshots
5051
) where
5152

5253
import Cardano.Binary as CBOR
@@ -72,6 +73,7 @@ import qualified Data.Vector.Primitive as VP
7273
import Data.Void
7374
import Database.LSMTree (Session, Table)
7475
import qualified Database.LSMTree as LSM
76+
import qualified Debug.Trace as Debug
7577
import NoThunks.Class
7678
import Ouroboros.Consensus.Block
7779
import Ouroboros.Consensus.Config
@@ -119,16 +121,16 @@ toTxOutBytes st txout =
119121
in TxOutBytes $ LSM.RawBytes (VP.Vector 0 (PBA.sizeofByteArray barr) barr)
120122

121123
fromTxOutBytes :: IndexedMemPack (l EmptyMK) (TxOut l) => l EmptyMK -> TxOutBytes -> TxOut l
122-
fromTxOutBytes st (TxOutBytes (LSM.RawBytes (VP.Vector _ _ barr))) =
123-
case indexedUnpack st barr of
124+
fromTxOutBytes st (TxOutBytes (LSM.RawBytes (VP.Vector off _ barr))) =
125+
case Debug.trace ("TxOut Offset: " <> show off) $ indexedUnpackLeftOver' st barr of
124126
Left err ->
125127
error $
126128
unlines
127129
[ "There was an error deserializing a TxOut from the LSM backend."
128130
, "This will likely result in a restart-crash loop."
129131
, "The error: " <> show err
130132
]
131-
Right v -> v
133+
Right (v, consum) -> Debug.trace ("TxOut Consumed: " <> show consum) v
132134

133135
instance LSM.SerialiseValue TxOutBytes where
134136
serialiseValue = unTxOutBytes
@@ -148,16 +150,16 @@ toTxInBytes _ txin =
148150
in TxInBytes $ LSM.RawBytes (VP.Vector 0 (PBA.sizeofByteArray barr) barr)
149151

150152
fromTxInBytes :: MemPack (TxIn l) => Proxy l -> TxInBytes -> TxIn l
151-
fromTxInBytes _ (TxInBytes (LSM.RawBytes (VP.Vector _ _ barr))) =
152-
case unpack barr of
153+
fromTxInBytes _ (TxInBytes (LSM.RawBytes (VP.Vector off _ barr))) =
154+
case Debug.trace ("TxIn Offset: " <> show off) $ unpackLeftOver' barr of
153155
Left err ->
154156
error $
155157
unlines
156158
[ "There was an error deserializing a TxIn from the LSM backend."
157159
, "This will likely result in a restart-crash loop."
158160
, "The error: " <> show err
159161
]
160-
Right v -> v
162+
Right (v, consum) -> Debug.trace ("TxOut Consumed: " <> show consum) v
161163

162164
instance LSM.SerialiseKey TxInBytes where
163165
serialiseKey = unTxInBytes

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util/IndexedMemPack.hs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,8 @@ module Ouroboros.Consensus.Util.IndexedMemPack
1717
, indexedPackByteArray
1818
, indexedUnpackError
1919
, indexedUnpack
20+
, indexedUnpackLeftOver'
21+
, unpackLeftOver'
2022
) where
2123

2224
import qualified Control.Monad as Monad
@@ -87,6 +89,18 @@ indexedUnpackLeftOver idx b = do
8789
pure res
8890
{-# INLINEABLE indexedUnpackLeftOver #-}
8991

92+
indexedUnpackLeftOver' ::
93+
forall idx a b.
94+
(IndexedMemPack idx a, Buffer b, HasCallStack) => idx -> b -> Either SomeError (a, Int)
95+
indexedUnpackLeftOver' idx = first fromMultipleErrors . runFailAgg . indexedUnpackLeftOver idx
96+
{-# INLINEABLE indexedUnpackLeftOver' #-}
97+
98+
unpackLeftOver' ::
99+
forall a b.
100+
(MemPack a, Buffer b, HasCallStack) => b -> Either SomeError (a, Int)
101+
unpackLeftOver' = first fromMultipleErrors . runFailAgg . unpackLeftOver
102+
{-# INLINEABLE unpackLeftOver' #-}
103+
90104
errorLeftOver :: HasCallStack => String -> Int -> Int -> a
91105
errorLeftOver name consumedBytes len =
92106
error $

0 commit comments

Comments
 (0)