4
4
{-# LANGUAGE ScopedTypeVariables #-}
5
5
{-# LANGUAGE TypeApplications #-}
6
6
{-# LANGUAGE TypeOperators #-}
7
+ {-# OPTIONS_GHC -Wno-unused-imports -Wno-unused-top-binds -Wno-missing-export-lists #-}
7
8
8
9
module Ouroboros.Consensus.Cardano.StreamingLedgerTables where
9
10
10
- import Cardano.Ledger.BaseTypes (WithOrigin (.. ))
11
+ import Cardano.Ledger.BaseTypes (BlockNo ( .. ), EpochNo ( .. ), SlotNo ( .. ), WithOrigin (.. ))
11
12
import Cardano.Ledger.Binary
12
- import Cardano.Ledger.Core (eraDecoder )
13
+ import Cardano.Ledger.Core (ByronEra , Era , eraDecoder , toEraCBOR )
13
14
import qualified Cardano.Ledger.Shelley.API as SL
14
15
import qualified Cardano.Ledger.Shelley.LedgerState as SL
15
16
import qualified Cardano.Ledger.State as SL
17
+ import qualified Cardano.Protocol.TPraos.BHeader as SL
18
+ import Cardano.Slotting.Time
16
19
import Control.Monad.Except
17
20
import Control.Tracer (nullTracer )
18
21
import Data.ByteString (ByteString )
19
22
import qualified Data.Map.Strict as Map
23
+ import Data.MemPack
24
+ import Data.Proxy
20
25
import Data.SOP.BasicFunctors
21
26
import Data.SOP.Functors
22
27
import Data.SOP.Strict
23
28
import qualified Data.SOP.Telescope as Telescope
29
+ import qualified Debug.Trace as Debug
24
30
import Lens.Micro
25
31
import Ouroboros.Consensus.Byron.Ledger
26
32
import Ouroboros.Consensus.Cardano.Block
@@ -29,6 +35,7 @@ import Ouroboros.Consensus.Cardano.Ledger
29
35
import Ouroboros.Consensus.HardFork.Combinator
30
36
import Ouroboros.Consensus.HardFork.Combinator.Basics (LedgerState (.. ))
31
37
import Ouroboros.Consensus.HardFork.Combinator.State
38
+ import Ouroboros.Consensus.HardFork.History.Summary
32
39
import Ouroboros.Consensus.Ledger.Abstract
33
40
import Ouroboros.Consensus.Ledger.Tables.Utils (emptyLedgerTables )
34
41
import Ouroboros.Consensus.Shelley.Ledger
@@ -38,17 +45,24 @@ import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB
38
45
import Ouroboros.Consensus.Util.IOLike (bracket )
39
46
import Ouroboros.Consensus.Util.StreamingLedgerTables
40
47
import Streaming
48
+ import System.Directory
41
49
import System.FS.API
42
50
import System.FS.IO
51
+ import System.FilePath as FilePath
52
+ import System.IO.Temp
53
+ import qualified Test.Cardano.Ledger.Conway.Examples as Conway
54
+ import Test.Cardano.Protocol.TPraos.Examples
55
+
56
+ type L = LedgerState (CardanoBlock StandardCrypto )
43
57
44
58
fromInMemory ::
45
59
SomeHasFS IO ->
46
60
FsPath ->
47
61
LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
48
62
( Stream
49
63
( Of
50
- ( TxIn ( LedgerState ( CardanoBlock StandardCrypto ))
51
- , TxOut ( LedgerState ( CardanoBlock StandardCrypto ))
64
+ ( TxIn L
65
+ , TxOut L
52
66
)
53
67
)
54
68
(ExceptT DeserialiseFailure IO )
@@ -63,27 +77,25 @@ fromInMemory shfs fp (HardForkLedgerState (HardForkState idx)) k =
63
77
(Current (Flip LedgerState EmptyMK ) -.-> K (ExceptT DeserialiseFailure IO () ))
64
78
(CardanoEras StandardCrypto )
65
79
np =
66
- ( Fn $ undefined ::
67
- (Current (Flip LedgerState EmptyMK ) -.-> K (ExceptT DeserialiseFailure IO () )) ByronBlock
68
- )
69
- :* (Fn $ K . foo ShelleyTxOut . unFlip . currentState)
70
- :* (Fn $ K . foo AllegraTxOut . unFlip . currentState)
71
- :* (Fn $ K . foo MaryTxOut . unFlip . currentState)
72
- :* (Fn $ K . foo AlonzoTxOut . unFlip . currentState)
73
- :* (Fn $ K . foo BabbageTxOut . unFlip . currentState)
74
- :* (Fn $ K . foo ConwayTxOut . unFlip . currentState)
75
- :* (Fn $ K . foo DijkstraTxOut . unFlip . currentState)
80
+ (Fn $ const $ K $ pure () )
81
+ :* (Fn $ K . fromEra ShelleyTxOut . unFlip . currentState)
82
+ :* (Fn $ K . fromEra AllegraTxOut . unFlip . currentState)
83
+ :* (Fn $ K . fromEra MaryTxOut . unFlip . currentState)
84
+ :* (Fn $ K . fromEra AlonzoTxOut . unFlip . currentState)
85
+ :* (Fn $ K . fromEra BabbageTxOut . unFlip . currentState)
86
+ :* (Fn $ K . fromEra ConwayTxOut . unFlip . currentState)
87
+ :* (Fn $ K . fromEra DijkstraTxOut . unFlip . currentState)
76
88
:* Nil
77
89
in
78
90
hcollapse $ hap np $ Telescope. tip idx
79
91
where
80
- foo ::
92
+ fromEra ::
81
93
forall proto era .
82
94
ShelleyCompatible proto era =>
83
95
(TxOut (LedgerState (ShelleyBlock proto era )) -> CardanoTxOut StandardCrypto ) ->
84
96
LedgerState (ShelleyBlock proto era ) EmptyMK ->
85
97
ExceptT DeserialiseFailure IO ()
86
- foo toCardanoTxOut st =
98
+ fromEra toCardanoTxOut st =
87
99
let certInterns =
88
100
internsFromMap $
89
101
shelleyLedgerState st
@@ -105,28 +117,95 @@ toLMDB ::
105
117
FilePath ->
106
118
Stream
107
119
( Of
108
- ( TxIn ( LedgerState ( CardanoBlock StandardCrypto ))
109
- , TxOut ( LedgerState ( CardanoBlock StandardCrypto ))
120
+ ( TxIn L
121
+ , TxOut L
110
122
)
111
123
)
112
124
(ExceptT DeserialiseFailure IO )
113
125
(Stream (Of ByteString ) IO () ) ->
114
126
ExceptT DeserialiseFailure IO (Stream (Of ByteString ) IO () )
115
127
toLMDB hint fp s = do
128
+ tempDir <- lift $ getCanonicalTemporaryDirectory
129
+ let lmdbTemp = tempDir FilePath. </> " lmdb_streaming"
130
+ lift $ removePathForcibly lmdbTemp
131
+ currDir <- lift $ getCurrentDirectory
132
+ lift $ System.Directory. createDirectory lmdbTemp
116
133
bs <-
117
134
lift $
118
135
LMDB. newLMDBBackingStore
119
136
nullTracer
120
137
limits
121
- (LiveLMDBFS $ SomeHasFS $ ioHasFS $ MountPoint fp )
122
- (SnapshotsFS $ SomeHasFS $ ioHasFS $ MountPoint fp )
138
+ (LiveLMDBFS $ SomeHasFS $ ioHasFS $ MountPoint lmdbTemp )
139
+ (SnapshotsFS $ SomeHasFS $ ioHasFS $ MountPoint currDir )
123
140
(InitFromValues (At 0 ) hint emptyLedgerTables)
124
141
r <- sinkLmdbS @ (ExceptT DeserialiseFailure IO ) 1000 hint (\ s' h d -> lift $ bsWrite bs s' h d) s
142
+ lift $ bsCopy bs hint (mkFsPath (splitDirectories fp))
125
143
lift $ bsClose bs
126
144
pure r
127
145
146
+ fromLMDB ::
147
+ LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
148
+ FilePath ->
149
+ Stream (Of (TxIn L , TxOut L )) (ExceptT DeserialiseFailure IO ) ()
150
+ fromLMDB hint fp = do
151
+ tempDir <- lift $ lift $ getCanonicalTemporaryDirectory
152
+ let lmdbTemp = tempDir FilePath. </> " lmdb_streaming"
153
+ lift $ lift $ removePathForcibly lmdbTemp
154
+ Debug. traceM " Deleted directory"
155
+ currDir <- lift $ lift $ getCurrentDirectory
156
+ lift $ lift $ System.Directory. createDirectory lmdbTemp
157
+ bs <-
158
+ lift $
159
+ lift $
160
+ LMDB. newLMDBBackingStore
161
+ nullTracer
162
+ limits
163
+ (LiveLMDBFS $ SomeHasFS $ ioHasFS $ MountPoint lmdbTemp)
164
+ (SnapshotsFS $ SomeHasFS $ ioHasFS $ MountPoint currDir)
165
+ (InitFromCopy hint (mkFsPath (splitDirectories fp)))
166
+ Debug. traceM " Opened LMDB"
167
+ bsvh <- lift $ lift $ bsValueHandle bs
168
+ Debug. traceM " Opened value handle"
169
+ yieldLmdbS 1000 hint bsvh
170
+
171
+ toInMemory ::
172
+ L EmptyMK ->
173
+ FilePath ->
174
+ Stream (Of (TxIn L , TxOut L )) (ExceptT DeserialiseFailure IO ) () ->
175
+ ExceptT DeserialiseFailure IO ()
176
+ toInMemory (HardForkLedgerState (HardForkState idx)) fp s = do
177
+ currDir <- lift $ getCurrentDirectory
178
+ let
179
+ np =
180
+ (Fn $ const $ K $ encOne (Proxy @ ByronEra ) currDir)
181
+ :* (Fn $ const $ K $ encOne (Proxy @ ShelleyEra ) currDir)
182
+ :* (Fn $ const $ K $ encOne (Proxy @ AllegraEra ) currDir)
183
+ :* (Fn $ const $ K $ encOne (Proxy @ MaryEra ) currDir)
184
+ :* (Fn $ const $ K $ encOne (Proxy @ AlonzoEra ) currDir)
185
+ :* (Fn $ const $ K $ encOne (Proxy @ BabbageEra ) currDir)
186
+ :* (Fn $ const $ K $ encOne (Proxy @ ConwayEra ) currDir)
187
+ :* (Fn $ const $ K $ encOne (Proxy @ DijkstraEra ) currDir)
188
+ :* Nil
189
+ hcollapse $ hap np $ Telescope. tip idx
190
+ where
191
+ encOne :: forall era . Era era => Proxy era -> FilePath -> ExceptT DeserialiseFailure IO ()
192
+ encOne _ currDir =
193
+ sinkInMemoryS
194
+ (Proxy @ L )
195
+ 1000
196
+ (toEraCBOR @ era . encodeMemPack)
197
+ (toEraCBOR @ era . eliminateCardanoTxOut (const encodeMemPack))
198
+ (SomeHasFS $ ioHasFS $ MountPoint currDir)
199
+ fp
200
+ s
201
+
128
202
limits :: LMDB. LMDBLimits
129
- limits = undefined
203
+ limits =
204
+ LMDB. LMDBLimits
205
+ { LMDB. lmdbMapSize = 16 * 1024 * 1024 * 1024
206
+ , LMDB. lmdbMaxDatabases = 10
207
+ , LMDB. lmdbMaxReaders = 16
208
+ }
130
209
131
210
foo ::
132
211
SomeHasFS IO ->
@@ -135,3 +214,41 @@ foo ::
135
214
LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
136
215
ExceptT DeserialiseFailure IO ()
137
216
foo shfs fpFrom fpTo st = fromInMemory shfs fpFrom st (toLMDB st fpTo)
217
+
218
+ bar ::
219
+ LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
220
+ FilePath ->
221
+ FilePath ->
222
+ ExceptT DeserialiseFailure IO ()
223
+ bar st fpFrom fpTo = do
224
+ let s = fromLMDB st fpFrom
225
+ toInMemory st fpTo s
226
+
227
+ lstate :: L EmptyMK
228
+ lstate =
229
+ HardForkLedgerState
230
+ $ HardForkState
231
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
232
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
233
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
234
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
235
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
236
+ $ TS (K $ Past (Bound (RelativeTime 0 ) 0 (EpochNo 0 )) (Bound (RelativeTime 0 ) 0 (EpochNo 0 )))
237
+ $ TZ
238
+ $ Current
239
+ (Bound (RelativeTime 0 ) 0 (EpochNo 0 ))
240
+ $ Flip
241
+ ShelleyLedgerState
242
+ { shelleyLedgerTip =
243
+ At
244
+ ShelleyTip
245
+ { shelleyTipSlotNo = SlotNo 9
246
+ , shelleyTipBlockNo = BlockNo 3
247
+ , shelleyTipHash =
248
+ ShelleyHash $ SL. unHashHeader $ pleHashHeader $ ledgerExamplesTPraos Conway. ledgerExamples
249
+ }
250
+ , shelleyLedgerState =
251
+ leNewEpochState $ pleLedgerExamples $ ledgerExamplesTPraos Conway. ledgerExamples
252
+ , shelleyLedgerTransition = ShelleyTransitionInfo {shelleyAfterVoting = 0 }
253
+ , shelleyLedgerTables = emptyLedgerTables
254
+ }
0 commit comments