Skip to content

Commit

Permalink
feedback/CI for PR #6054
Browse files Browse the repository at this point in the history
  • Loading branch information
mgmeier committed Dec 16, 2024
1 parent d500fd1 commit d6fc781
Show file tree
Hide file tree
Showing 7 changed files with 19 additions and 68 deletions.
3 changes: 3 additions & 0 deletions bench/locli/locli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,9 @@ common project-config
-Wcompat
-Wno-all-missed-specialisations

if impl(ghc >= 9.8)
ghc-options: -Wno-x-partial

build-depends: base >= 4.14 && < 5,

if os(windows)
Expand Down
1 change: 0 additions & 1 deletion bench/locli/src/Cardano/Analysis/API/Ground.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Analysis.API.Ground
Expand Down
62 changes: 15 additions & 47 deletions bench/locli/src/Cardano/Analysis/BlockProp.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,9 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StrictData #-}

#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif

{-# OPTIONS_GHC -Wno-incomplete-patterns -Wno-name-shadowing #-}
{-# OPTIONS_GHC -Wno-unused-imports -Wno-partial-fields -Wno-unused-matches -Wno-incomplete-record-updates #-}

{- HLINT ignore "Avoid lambda" -}
{- HLINT ignore "Eta reduce" -}
{- HLINT ignore "Use head" -}

module Cardano.Analysis.BlockProp
( summariseMultiBlockProp
Expand All @@ -25,42 +17,18 @@ module Cardano.Analysis.BlockProp
)
where

import Prelude (String, (!!), error, head, last, id, show, tail, read)
import Cardano.Prelude hiding (head, show)

import Control.Arrow ((***), (&&&))
import Data.Aeson (ToJSON(..), FromJSON(..))
import Data.Bifunctor
import Data.Function (on)
import Data.List (break, dropWhileEnd, intercalate, partition, span)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe (catMaybes, mapMaybe, isNothing)
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text qualified as T
import Data.Text.Short (toText)
import Data.Tuple (swap)
import Data.Tuple.Extra (both, fst3, snd3, thd3)
import Data.Vector (Vector)
import Data.Vector qualified as Vec

import Data.Time.Clock (NominalDiffTime, UTCTime, addUTCTime, diffUTCTime)

import Text.Printf (printf)

import Cardano.Slotting.Slot (EpochNo(..), SlotNo(..))
import Ouroboros.Network.Block (BlockNo(..))

import Data.Accum
import Data.CDF
import Cardano.Analysis.API
import Cardano.Prelude hiding (head, show)
import Cardano.Unlog.LogObject
import Cardano.Util

import Cardano.Render
import Cardano.Unlog.LogObject
import Cardano.Unlog.Resources
import Cardano.Util
import Prelude (id, read, show)

import Cardano.Analysis.API
import Data.List (partition)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Tuple.Extra (both, fst3, snd3, thd3)


summariseMultiBlockProp :: [Centile] -> [BlockPropOne] -> Either CDFError MultiBlockProp
Expand Down Expand Up @@ -300,7 +268,7 @@ blockEventsAcceptance :: Genesis -> [ChainFilter] -> BlockEvents -> [(ChainFilte
blockEventsAcceptance genesis flts be = flts <&> (id &&& testBlockEvents genesis be)

rebuildChain :: Run -> [ChainFilter] -> [FilterName] -> [(LogObjectSource, MachView)] -> Chain
rebuildChain run@Run{genesis} flts fltNames xs@(fmap snd -> machViews) =
rebuildChain Run{genesis} flts _fltNames (fmap snd -> machViews) =
Chain
{ cDomSlots = DataDomain
(Interval (blk0 & beSlotNo) (blkL & beSlotNo) <&> I)
Expand Down Expand Up @@ -406,7 +374,7 @@ rebuildChain run@Run{genesis} flts fltNames xs@(fmap snd -> machViews) =
[ "No forger for hash ", show hash
, "\nErrors:\n"
] ++ intercalate "\n" (show <$> ers)
blkEvs@(forgerEv:_, oEvs, ers) ->
(forgerEv:_, oEvs, ers) ->
go (bfePrevBlock forgerEv) (liftBlockEvents forgerEv oEvs ers : acc)

liftBlockEvents :: ForgerEvents NominalDiffTime -> [ObserverEvents NominalDiffTime] -> [BPError] -> BlockEvents
Expand Down Expand Up @@ -536,7 +504,7 @@ renderBlockPropError = \case
rejs

blockProp :: Run -> Chain -> Either BlockPropError BlockPropOne
blockProp run@Run{genesis} Chain{..} = do
blockProp _ Chain{..} = do
(c :: [BlockEvents]) <-
case filter (all snd . beAcceptance) cMainChain of
[] -> Left $
Expand Down Expand Up @@ -626,7 +594,7 @@ blockProp run@Run{genesis} Chain{..} = do

-- | Given a single machine's log object stream, recover its block map.
blockEventMapsFromLogObjects :: Run -> (LogObjectSource, [LogObject]) -> MachView
blockEventMapsFromLogObjects run (f, []) =
blockEventMapsFromLogObjects _ (f, []) =
error $ mconcat ["0 LogObjects in ", logObjectSourceFile f]
blockEventMapsFromLogObjects run (f, xs@(x:_)) =
foldl' (blockPropMachEventsStep run f) initial xs
Expand All @@ -645,7 +613,7 @@ blockEventMapsFromLogObjects run (f, xs@(x:_)) =
}

blockPropMachEventsStep :: Run -> LogObjectSource -> MachView -> LogObject -> MachView
blockPropMachEventsStep run@Run{genesis} _ mv@MachView{..} lo = case lo of
blockPropMachEventsStep Run{genesis} _ mv@MachView{..} lo = case lo of
-- 0. Notice (observer only)
LogObject{loAt, loHost, loBody=LOChainSyncClientSeenHeader{loBlock,loBlockNo,loSlotNo}} ->
let mbe0 = getBlock loBlock
Expand Down
6 changes: 1 addition & 5 deletions bench/locli/src/Cardano/Analysis/MachPerf.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,8 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE MultiWayIf #-}

#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif

{-# OPTIONS_GHC -Wno-incomplete-patterns -Wno-name-shadowing #-}

{- HLINT ignore "Use head" -}
{- HLINT ignore "Evaluate" -}

Expand Down
5 changes: 0 additions & 5 deletions bench/locli/src/Cardano/Analysis/Summary.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE UndecidableInstances #-}

#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif

{-# OPTIONS_GHC -Wno-name-shadowing -Wno-orphans #-}

{- HLINT ignore "Use mapMaybe" -}
Expand Down
5 changes: 0 additions & 5 deletions bench/locli/src/Cardano/Render.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}

#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif

{- HLINT ignore "Use concatMap" -}
{- HLINT ignore "Use fromMaybe" -}

Expand Down
5 changes: 0 additions & 5 deletions bench/locli/test/Test/Analysis/CDF.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}

#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif

module Test.Analysis.CDF where

import Cardano.Prelude hiding (handle, head)
Expand Down

0 comments on commit d6fc781

Please sign in to comment.