Skip to content

Commit faf363e

Browse files
committed
Linear Leios: fixup CI failures
1 parent d569cd2 commit faf363e

File tree

24 files changed

+383
-359
lines changed

24 files changed

+383
-359
lines changed

analysis/sims/trace-processor/src/Leios/Tracing/Cpu.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,7 @@ import System.IO (IOMode (WriteMode), hClose, hPutStrLn, openFile)
2121

2222
import qualified Data.Text as T (unpack)
2323

24-
data ItemKey
25-
= ItemKey
24+
data ItemKey = ItemKey
2625
{ slot :: Int
2726
, node :: Text
2827
, task :: Text

analysis/sims/trace-processor/src/Leios/Tracing/Lifecycle.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -28,15 +28,13 @@ import qualified Data.Map.Strict as M (elems, fromList, insertWith, restrictKeys
2828
import qualified Data.Set as S (map, singleton)
2929
import qualified Data.Text as T (unpack)
3030

31-
data ItemKey
32-
= ItemKey
31+
data ItemKey = ItemKey
3332
{ kind :: Text
3433
, item :: Text
3534
}
3635
deriving (Eq, Ord, Show)
3736

38-
data ItemInfo
39-
= ItemInfo
37+
data ItemInfo = ItemInfo
4038
{ size :: Minimum Int
4139
, references :: Sum Int
4240
, created :: Minimum Double

analysis/sims/trace-processor/src/Leios/Tracing/Receipt.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -26,15 +26,13 @@ import System.IO (IOMode (WriteMode), hClose, hPutStrLn, openFile)
2626
import qualified Data.Map.Strict as M (insertWith, (!))
2727
import qualified Data.Text as T (unpack)
2828

29-
data ItemKey
30-
= ItemKey
29+
data ItemKey = ItemKey
3130
{ kind :: Text
3231
, item :: Text
3332
}
3433
deriving (Eq, Ord, Show)
3534

36-
data ItemInfo
37-
= ItemInfo
35+
data ItemInfo = ItemInfo
3836
{ producer :: Text
3937
, sent :: Minimum Double
4038
, size :: Maximum Double

analysis/sims/trace-processor/src/Leios/Tracing/Resource.hs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,13 @@ import Leios.Tracing.Util (Maximum (..))
2525
import qualified Data.Map.Strict as M (insertWith, map, mapKeysWith, toList)
2626
import qualified Data.Text as T (unpack)
2727

28-
data ItemKey'
29-
= ItemKey'
28+
data ItemKey' = ItemKey'
3029
{ slot' :: Int
3130
, node' :: Text
3231
}
3332
deriving (Eq, Ord, Show)
3433

35-
data ItemInfo'
36-
= ItemInfo'
34+
data ItemInfo' = ItemInfo'
3735
{ egress' :: Sum Double
3836
, disk' :: Sum Double
3937
, cpu' :: Sum Double
@@ -58,14 +56,12 @@ instance Monoid ItemInfo' where
5856

5957
type Index' = Map ItemKey' ItemInfo'
6058

61-
newtype ItemKey
62-
= ItemKey
59+
newtype ItemKey = ItemKey
6360
{ node :: Text
6461
}
6562
deriving (Eq, Ord, Show)
6663

67-
data ItemInfo
68-
= ItemInfo
64+
data ItemInfo = ItemInfo
6965
{ egress :: Sum Double
7066
, disk :: Sum Double
7167
, totalCpu :: Sum Double

data/simulation/config.default.yaml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,9 @@ eb-max-age-for-relay-slots: 40
177177
# Only relevant when running with the "full-without-ibs" variant.
178178
eb-referenced-txs-max-size-bytes: 16384000
179179

180+
# For Linear Leios
181+
eb-body-avg-size-bytes: 2500000
182+
180183
################################################################################
181184
# Vote Configuration
182185
################################################################################

leios-trace-verifier/hs-src/test/Spec/Transition.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,8 +23,7 @@ import qualified Data.Set as S
2323
import qualified Data.Text as T
2424
import qualified Spec.Scenario as Scenario (config, idOther, idSut)
2525

26-
data TracingContext
27-
= TracingContext
26+
data TracingContext = TracingContext
2827
{ _clock :: Time
2928
, _slotNo :: SlotNo
3029
, _rbs :: Map Text Text

simulation/src/Chan/Mux.hs

Lines changed: 25 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,9 @@ import Control.Monad (forM_, forever)
2828
import Control.Monad.Class.MonadFork (MonadFork (forkIO))
2929
import Control.Tracer (Tracer (Tracer), traceWith)
3030
import Data.Array (Array, listArray, (!))
31-
import Data.Kind
3231
import Data.Foldable (traverse_)
3332
import Data.Functor.Const (Const (Const), getConst)
33+
import Data.Kind
3434
import STMCompat
3535

3636
class ConnectionBundle bundle where
@@ -48,8 +48,7 @@ class ConnectionBundle bundle where
4848
-- 'toBundleMsg'. For example, a valid implementation would be:
4949
--
5050
-- > ToFromBundleMsg toDynamic (fromJust . fromDynamic)
51-
data ToFromBundleMsg mm a
52-
= ToFromBundleMsg
51+
data ToFromBundleMsg mm a = ToFromBundleMsg
5352
{ toBundleMsg :: a -> mm
5453
, fromBundleMsg :: mm -> a
5554
}
@@ -68,9 +67,10 @@ data BorneMsg a = BorneMsg !Int a
6867
-- The mini protocols never see this, so this type is not exported. It does
6968
-- occur in the argument types of some exported functions, but the caller
7069
-- should be using parametric functions to generate those arguments.
71-
data BearerMsg a = BearerMsg !Bytes [BorneMsg a]
72-
-- ^ the cumulative size of the slices the borne messages whose /final/ slice
73-
-- is in this message
70+
data BearerMsg a
71+
= -- | the cumulative size of the slices the borne messages whose /final/ slice
72+
-- is in this message
73+
BearerMsg !Bytes [BorneMsg a]
7474

7575
instance MessageSize (BearerMsg a) where
7676
messageSizeBytes (BearerMsg sz _) = 1 + sz
@@ -140,7 +140,7 @@ newMuxChanSingle
140140
takeMVar sendLock
141141
atomically $
142142
writeTQueue sendQueue $
143-
(sendLock, messageSizeBytes bundleMsg, muxmsg)
143+
(sendLock, messageSizeBytes bundleMsg, muxmsg)
144144
}
145145

146146
data RecvQueue m mm where
@@ -167,20 +167,20 @@ muxer ::
167167
TQueue m (MVar m (), Bytes, BorneMsg (BundleMsg bundle)) ->
168168
m ()
169169
muxer bearer sendQueue =
170-
forever $ do
171-
x <- atomically (readTQueue sendQueue)
172-
(muxmsg, locks) <- go 0 [] [] x
173-
mapM_ (flip putMVar ()) locks
174-
writeChan bearer muxmsg
175-
where
176-
--- from ouroboros-network's @Network.Mux.Bearer.makeSocketBearer'@
177-
sliceBytes = 12288
178-
loafBytes = 131072
179-
180-
go !accBytes acc locks (lock, bytes, msg) = do
181-
let !accBytes' = accBytes + min sliceBytes bytes
182-
(acc', locks') <-
183-
if bytes <= sliceBytes
170+
forever $ do
171+
x <- atomically (readTQueue sendQueue)
172+
(muxmsg, locks) <- go 0 [] [] x
173+
mapM_ (flip putMVar ()) locks
174+
writeChan bearer muxmsg
175+
where
176+
--- from ouroboros-network's @Network.Mux.Bearer.makeSocketBearer'@
177+
sliceBytes = 12288
178+
loafBytes = 131072
179+
180+
go !accBytes acc locks (lock, bytes, msg) = do
181+
let !accBytes' = accBytes + min sliceBytes bytes
182+
(acc', locks') <-
183+
if bytes <= sliceBytes
184184
then do
185185
-- We do not release the lock before finalizing the loaf because a
186186
-- single loaf should include slices from at most one borne message
@@ -192,8 +192,10 @@ muxer bearer sendQueue =
192192
atomically $ writeTQueue sendQueue (lock, bytes', msg)
193193
pure (acc, locks)
194194

195-
let result = (BearerMsg accBytes' acc', locks')
196-
if accBytes' >= loafBytes then pure result else do
195+
let result = (BearerMsg accBytes' acc', locks')
196+
if accBytes' >= loafBytes
197+
then pure result
198+
else do
197199
atomically (tryReadTQueue sendQueue) >>= \case
198200
Nothing -> pure result
199201
Just x -> go accBytes' acc' locks' x

simulation/src/Chan/TCP.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -38,8 +38,8 @@ data LabelTcpDir e = DirClientToServer e | DirServerToClient e
3838

3939
lensLabelTcpDir :: Functor f => (a -> f b) -> LabelTcpDir a -> f (LabelTcpDir b)
4040
lensLabelTcpDir f = \case
41-
DirClientToServer x -> DirClientToServer <$> f x
42-
DirServerToClient x -> DirServerToClient <$> f x
41+
DirClientToServer x -> DirClientToServer <$> f x
42+
DirServerToClient x -> DirServerToClient <$> f x
4343

4444
-- | Class for messages to be sent over a simulated TCP connection.
4545
-- To correctly model the timing of the messages sent over the connection we

simulation/src/LeiosProtocol/RelayBuffer.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,7 @@ import Data.Word (Word64)
2222
---- Relay Buffer
2323
--------------------------------
2424

25-
data RelayBuffer key value
26-
= RelayBuffer
25+
data RelayBuffer key value = RelayBuffer
2726
{ entries :: !(FingerTree TicketRange (EntryWithTicket key value))
2827
, index :: !(Map key Ticket)
2928
, nextTicket :: !Ticket

simulation/src/LeiosProtocol/Short.hs

Lines changed: 25 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,10 @@ data RelayDiffusionConfig = RelayDiffusionConfig
9696
, maxBodiesToRequest :: !Word16
9797
}
9898

99-
data LeiosConfig = forall p. IsPipeline p => LeiosConfig
99+
data LeiosConfig
100+
= forall p.
101+
IsPipeline p =>
102+
LeiosConfig
100103
{ praos :: PraosConfig RankingBlockBody
101104
, pipeline :: SingPipeline p
102105
, sliceLength :: Int
@@ -230,7 +233,8 @@ convertConfig disk =
230233
certificateSize (Certificate votesMap) =
231234
fromIntegral $
232235
disk.certSizeBytesConstant
233-
+ disk.certSizeBytesPerNode `forEachKey` votesMap
236+
+ disk.certSizeBytesPerNode
237+
`forEachKey` votesMap
234238
sizes =
235239
SizesConfig
236240
{ inputBlockHeader = fromIntegral disk.ibHeadSizeBytes
@@ -240,27 +244,32 @@ convertConfig disk =
240244
, endorseBlock = \eb ->
241245
fromIntegral $
242246
disk.ebSizeBytesConstant
243-
+ disk.ebSizeBytesPerIb `forEach` eb.inputBlocks
247+
+ disk.ebSizeBytesPerIb
248+
`forEach` eb.inputBlocks
244249
-- TODO: make it a per-ref field.
245-
+ disk.ebSizeBytesPerIb `forEach` eb.endorseBlocksEarlierPipeline
250+
+ disk.ebSizeBytesPerIb
251+
`forEach` eb.endorseBlocksEarlierPipeline
246252
, voteMsg = \vt ->
247253
fromIntegral $
248254
disk.voteBundleSizeBytesConstant
249-
+ disk.voteBundleSizeBytesPerEb `forEach` vt.endorseBlocks
255+
+ disk.voteBundleSizeBytesPerEb
256+
`forEach` vt.endorseBlocks
250257
, certificate = \_cert ->
251258
fromIntegral $
252-
assert (0 == disk.certSizeBytesPerNode) $ -- TODO
259+
assert (0 == disk.certSizeBytesPerNode) $ -- TODO
253260
disk.certSizeBytesConstant
254261
, rankingBlockLegacyPraosPayloadAvgSize = fromIntegral disk.rbBodyLegacyPraosPayloadAvgSizeBytes
255262
}
256263
certificateGeneration (Certificate votesMap) =
257264
durationMsToDiffTime $
258265
disk.certGenerationCpuTimeMsConstant
259-
+ disk.certGenerationCpuTimeMsPerNode `forEachKey` votesMap
266+
+ disk.certGenerationCpuTimeMsPerNode
267+
`forEachKey` votesMap
260268
certificateValidation (Certificate votesMap) =
261269
durationMsToDiffTime $
262270
disk.certValidationCpuTimeMsConstant
263-
+ disk.certValidationCpuTimeMsPerNode `forEachKey` votesMap
271+
+ disk.certValidationCpuTimeMsPerNode
272+
`forEachKey` votesMap
264273
delays =
265274
LeiosDelays
266275
{ inputBlockGeneration = const $ durationMsToDiffTime disk.ibGenerationCpuTimeMs
@@ -282,13 +291,14 @@ convertConfig disk =
282291
durationMsToDiffTime $
283292
sum
284293
[ disk.voteGenerationCpuTimeMsConstant
285-
+ disk.voteGenerationCpuTimeMsPerIb `forEach` eb.inputBlocks
294+
+ disk.voteGenerationCpuTimeMsPerIb
295+
`forEach` eb.inputBlocks
286296
| eb <- ebs
287297
]
288298
, linearVoteMsgGeneration = \vm ibs ->
289299
assert (1 == length vm.endorseBlocks) $
290300
assert (vm.endorseBlocks == map (convertLinearId . (.id)) ibs) $
291-
assert (0 == disk.voteGenerationCpuTimeMsPerTx) $ -- TODO
301+
assert (0 == disk.voteGenerationCpuTimeMsPerTx) $ -- TODO
292302
durationMsToDiffTime $
293303
disk.voteGenerationCpuTimeMsConstant `forEach` ibs
294304
, voteMsgValidation = \vm ->
@@ -343,12 +353,12 @@ delaysAndSizesAsFull cfg@LeiosConfig{pipeline, voteSendStage} =
343353
, let EndorseBlock{..} = fullEB
344354
]
345355
fullLinearEBsVotedFor =
346-
[ InputBlock {
347-
body = fullIB.body
348-
, header =
356+
[ InputBlock
357+
{ body = fullIB.body
358+
, header =
349359
let InputBlockHeader{..} = fullIB.header
350-
in InputBlockHeader {id = unconvertLinearId id', ..}
351-
}
360+
in InputBlockHeader{id = unconvertLinearId id', ..}
361+
}
352362
| id' <- fullVT.endorseBlocks
353363
]
354364
fullRB = mockFullRankingBlock cfg

0 commit comments

Comments
 (0)