diff --git a/.github/mergify.yml b/.github/mergify.yml index 3ff7c231c6..fc83bd825f 100644 --- a/.github/mergify.yml +++ b/.github/mergify.yml @@ -5,7 +5,8 @@ pull_request_rules: method: squash name: Automatically merge pull requests conditions: - - status-success=bench (8.10.3, ubuntu-latest) + - status-success=bench-example (8.10.3, ubuntu-latest, Cabal-3.0.0.0) + - status-success=bench-example (8.10.3, ubuntu-latest, lsp-types-1.0.0.1) - status-success=nix (default, ubuntu-latest) - status-success=nix (default, macOS-latest) diff --git a/.github/workflows/bench.yml b/.github/workflows/bench.yml index e171256395..217bc40d6c 100644 --- a/.github/workflows/bench.yml +++ b/.github/workflows/bench.yml @@ -2,7 +2,7 @@ name: Benchmark on: [pull_request] jobs: - bench: + bench-init: runs-on: ${{ matrix.os }} strategy: @@ -38,20 +38,80 @@ jobs: - name: Build shell: bash - # Retry it three times to workaround compiler segfaults in windows - run: cabal build ghcide:benchHist || cabal build ghcide:benchHist || cabal build ghcide:benchHist + run: cabal build ghcide:benchHist + + - name: Bench init + shell: bash + run: cabal bench ghcide:benchHist -j --benchmark-options="all-binaries" + + # tar is required to preserve file permissions + # compression speeds up upload/download nicely + - name: tar workspace + shell: bash + run: tar -czf workspace.tar.gz * .git + + - name: tar cabal + run: | + cd ~/.cabal + tar -czf cabal.tar.gz * + + - name: Upload workspace + uses: actions/upload-artifact@v2 + with: + name: workspace + retention-days: 1 + path: workspace.tar.gz + + - name: Upload .cabal + uses: actions/upload-artifact@v2 + with: + name: cabal-home + retention-days: 1 + path: ~/.cabal/cabal.tar.gz + + bench-example: + needs: [bench-init] + runs-on: ${{ matrix.os }} + + strategy: + fail-fast: false + matrix: + ghc: ['8.10.3'] + os: [ubuntu-latest] + example: ['Cabal-3.0.0.0', 'lsp-types-1.0.0.1'] + + steps: + - uses: haskell/actions/setup@v1 + with: + ghc-version: ${{ matrix.ghc }} + cabal-version: '3.2' + enable-stack: false + + - name: Download cabal home + uses: actions/download-artifact@v2 + with: + name: cabal-home + path: . + + - name: Download workspace + uses: actions/download-artifact@v2 + with: + name: workspace + path: . + + - name: untar + run: | + tar xzf workspace.tar.gz + tar xzf cabal.tar.gz --directory ~/.cabal - name: Bench shell: bash - # run the tests without parallelism, otherwise tasty will attempt to run - # all test cases simultaneously which causes way too many hls - # instances to be spun up for the poor github actions runner to handle - run: cabal bench ghcide:benchHist + run: cabal bench ghcide:benchHist -j --benchmark-options="${{ matrix.example }}" - name: Display results shell: bash run: | - column -s, -t < ghcide/bench-results/results.csv | tee ghcide/bench-results/results.txt + column -s, -t < ghcide/bench-results/unprofiled/${{ matrix.example }}/results.csv | tee ghcide/bench-results/unprofiled/${{ matrix.example }}/results.txt - name: Archive benchmarking artifacts uses: actions/upload-artifact@v2 diff --git a/ghcide/.hlint.yaml b/ghcide/.hlint.yaml index 244d381490..40699c9b75 100644 --- a/ghcide/.hlint.yaml +++ b/ghcide/.hlint.yaml @@ -97,7 +97,7 @@ - flags: - default: false - {name: [-Wno-missing-signatures, -Wno-orphans, -Wno-overlapping-patterns, -Wno-incomplete-patterns, -Wno-missing-fields, -Wno-unused-matches]} - - {name: [-Wno-dodgy-imports,-Wno-incomplete-uni-patterns], within: [Main, Development.IDE.GHC.Compat]} + - {name: [-Wno-dodgy-imports,-Wno-incomplete-uni-patterns], within: [Main, Development.IDE.GHC.Compat, Development.Benchmark.Rules]} # - modules: # - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set' # - {name: Control.Arrow, within: []} # Certain modules are banned entirely diff --git a/ghcide/bench/README.md b/ghcide/bench/README.md index d3b3da1db3..783ab70985 100644 --- a/ghcide/bench/README.md +++ b/ghcide/bench/README.md @@ -6,10 +6,64 @@ performance analysis of ghcide: - `exe/Main.hs` - a standalone benchmark runner. Run with `stack run ghcide-bench` - `hist/Main.hs` - a Shake script for running the benchmark suite over a set of commits. - - Run with `stack bench` or `cabal bench`, + - Run with `stack bench ghcide` or `cabal bench ghcide`, - Requires a `ghcide-bench` binary in the PATH (usually provided by stack/cabal), - Calls `cabal` (or `stack`, configurable) internally to build the project, - - Driven by the `config.yaml` configuration file. + - Driven by the `bench/config.yaml` configuration file. By default it compares HEAD with "master" -Further details available in the config file and the module header comments. +# Examples and experiments + +The benchmark suites runs a set of experiments (hover, completion, edit, etc.) +over all the defined examples (currently Cabal and lsp-types). Examples are defined +in `ghcide/bench/config.yaml` whereas experiments are coded in `ghcide/bench/lib/Experiments.hs`. + +# Phony targets + +The Shake script supports a number of phony targets that allow running a subset of the benchmarks: + +* all +: runs all the examples, unprofiled + +* profiled-all +: runs all the examples with heap profiling, assuming `profilingInterval` is defined + +* Cabal-3.0.0.0 +: runs the Cabal example, unprofiled + +* profiled-Cabal-3.0.0.0 +: runs the Cabal example, with heap profiling + +* etc + +`--help` lists all the phony targets. Invoke it with: + + cabal bench ghcide --benchmark-options="--help" + +``` +Targets: + - bench-results/binaries/*/commitid + - bench-results/binaries/HEAD/ghcide + - bench-results/binaries/HEAD/ghc.path + - bench-results/binaries/*/ghcide + - bench-results/binaries/*/ghc.path + - bench-results/binaries/*/*.warmup + - bench-results/*/*/*/*.csv + - bench-results/*/*/*/*.gcStats.log + - bench-results/*/*/*/*.output.log + - bench-results/*/*/*/*.eventlog + - bench-results/*/*/*/*.hp + - bench-results/*/*/*/results.csv + - bench-results/*/*/results.csv + - bench-results/*/results.csv + - bench-results/*/*/*/*.svg + - bench-results/*/*/*/*.diff.svg + - bench-results/*/*/*.svg + - bench-results/*/*/*/*.heap.svg + - Cabal-3.0.0.0 + - lsp-types-1.0.0.1 + - all + - profiled-Cabal-3.0.0.0 + - profiled-lsp-types-1.0.0.1 + - profiled-all + ``` diff --git a/ghcide/bench/config.yaml b/ghcide/bench/config.yaml index 540d20f174..a174b641c0 100644 --- a/ghcide/bench/config.yaml +++ b/ghcide/bench/config.yaml @@ -67,3 +67,7 @@ versions: # - ghcide-v0.7.3 - upstream: origin/master - HEAD + +# Heap profile interval in seconds (+RTS -i) +# Comment out to disable heap profiling +profileInterval: 1 diff --git a/ghcide/bench/hist/Main.hs b/ghcide/bench/hist/Main.hs index c2e8f96cda..c34e2529a1 100644 --- a/ghcide/bench/hist/Main.hs +++ b/ghcide/bench/hist/Main.hs @@ -52,10 +52,16 @@ import qualified Experiments.Types as E import GHC.Generics (Generic) import Numeric.Natural (Natural) import Development.Shake.Classes +import System.Console.GetOpt +import Data.Maybe +import Control.Monad.Extra -config :: FilePath -config = "bench/config.yaml" +configPath :: FilePath +configPath = "bench/config.yaml" + +configOpt :: OptDescr (Either String FilePath) +configOpt = Option [] ["config"] (ReqArg Right configPath) "config file" -- | Read the config without dependency readConfigIO :: FilePath -> IO (Config BuildSystem) @@ -65,17 +71,17 @@ instance IsExample Example where getExampleName = E.getExampleName type instance RuleResult GetExample = Maybe Example type instance RuleResult GetExamples = [Example] +shakeOpts :: ShakeOptions +shakeOpts = + shakeOptions{shakeChange = ChangeModtimeAndDigestInput, shakeThreads = 0} + main :: IO () -main = shakeArgs shakeOptions {shakeChange = ChangeModtimeAndDigestInput, shakeThreads = 0} $ do - createBuildSystem $ \resource -> do - configStatic <- liftIO $ readConfigIO config - let build = outputFolder configStatic - buildRules build ghcideBuildRules - benchRules build resource (MkBenchRules (askOracle $ GetSamples ()) benchGhcide "ghcide") - csvRules build - svgRules build - heapProfileRules build - action $ allTargets build +main = shakeArgsWith shakeOpts [configOpt] $ \configs wants -> pure $ Just $ do + let config = fromMaybe configPath $ listToMaybe configs + _configStatic <- createBuildSystem config + case wants of + [] -> want ["all"] + _ -> want wants ghcideBuildRules :: MkBuildRules BuildSystem ghcideBuildRules = MkBuildRules findGhcForBuildSystem "ghcide" buildGhcide @@ -89,13 +95,14 @@ data Config buildSystem = Config versions :: [GitCommit], -- | Output folder ('foo' works, 'foo/bar' does not) outputFolder :: String, - buildTool :: buildSystem + buildTool :: buildSystem, + profileInterval :: Maybe Double } deriving (Generic, Show) deriving anyclass (FromJSON) -createBuildSystem :: (Resource -> Rules a) -> Rules a -createBuildSystem userRules = do +createBuildSystem :: FilePath -> Rules (Config BuildSystem ) +createBuildSystem config = do readConfig <- newCache $ \fp -> need [fp] >> liftIO (readConfigIO fp) _ <- addOracle $ \GetExperiments {} -> experiments <$> readConfig config @@ -105,9 +112,20 @@ createBuildSystem userRules = do _ <- addOracle $ \GetBuildSystem {} -> buildTool <$> readConfig config _ <- addOracle $ \GetSamples{} -> samples <$> readConfig config - benchResource <- newResource "ghcide-bench" 1 + configStatic <- liftIO $ readConfigIO config + let build = outputFolder configStatic + + buildRules build ghcideBuildRules + benchRules build (MkBenchRules (askOracle $ GetSamples ()) benchGhcide "ghcide") + csvRules build + svgRules build + heapProfileRules build + phonyRules "" "ghcide" NoProfiling build (examples configStatic) + + whenJust (profileInterval configStatic) $ \i -> do + phonyRules "profiled-" "ghcide" (CheapHeapProfiling i) build (examples configStatic) - userRules benchResource + return configStatic newtype GetSamples = GetSamples () deriving newtype (Binary, Eq, Hashable, NFData, Show) type instance RuleResult GetSamples = Natural diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index feadae9ee5..559efc2dc8 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -246,7 +246,9 @@ benchmark benchHist base == 4.*, shake-bench == 0.1.*, directory, + extra, filepath, + optparse-applicative, shake, text, yaml diff --git a/shake-bench/src/Development/Benchmark/Rules.hs b/shake-bench/src/Development/Benchmark/Rules.hs index 7d8e2752f4..cca1e7fa24 100644 --- a/shake-bench/src/Development/Benchmark/Rules.hs +++ b/shake-bench/src/Development/Benchmark/Rules.hs @@ -44,14 +44,16 @@ For diff graphs, the "previous version" is the preceding entry in the list of versions in the config file. A possible improvement is to obtain this info via `git rev-list`. -} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Development.Benchmark.Rules ( buildRules, MkBuildRules(..), - benchRules, MkBenchRules(..), BenchProject(..), + benchRules, MkBenchRules(..), BenchProject(..), ProfilingMode(..), csvRules, svgRules, heapProfileRules, - allTargets, + phonyRules, + allTargetsForExample, GetExample(..), GetExamples(..), IsExample(..), RuleResultForExample, GetExperiments(..), @@ -70,9 +72,9 @@ import Data.Aeson (FromJSON (..), ToJSON (..), Value (..), (.!=), (.:?)) -import Data.List (isInfixOf, find, transpose) +import Data.List (find, isInfixOf, stripPrefix, transpose) import Data.List.Extra (lower) -import Data.Maybe (fromMaybe) +import Data.Maybe (fromMaybe) import Data.Text (Text) import qualified Data.Text as T import Development.Shake @@ -92,9 +94,8 @@ import Text.Read (Read (..), get, readMaybe, readP_to_Prec) import Text.Printf -import Control.Monad.Extra -import qualified System.Directory as IO import Data.Char (isDigit) +import System.Time.Extra (Seconds) newtype GetExperiments = GetExperiments () deriving newtype (Binary, Eq, Hashable, NFData, Show) newtype GetVersions = GetVersions () deriving newtype (Binary, Eq, Hashable, NFData, Show) @@ -121,28 +122,53 @@ class (Binary e, Eq e, Hashable e, NFData e, Show e, Typeable e) => IsExample e -------------------------------------------------------------------------------- -allTargets :: RuleResultForExample e => FilePath -> Action () -allTargets buildFolder = do +allTargetsForExample :: IsExample e => ProfilingMode -> FilePath -> e -> Action [FilePath] +allTargetsForExample prof baseFolder ex = do experiments <- askOracle $ GetExperiments () - examples <- askOracle $ GetExamples () versions <- askOracle $ GetVersions () - need $ - [buildFolder getExampleName e "results.csv" | e <- examples ] ++ - [buildFolder "results.csv"] + let buildFolder = baseFolder profilingPath prof + return $ + [buildFolder getExampleName ex "results.csv"] ++ [ buildFolder getExampleName ex escaped (escapeExperiment e) <.> "svg" | e <- experiments - , ex <- examples ] ++ [ buildFolder getExampleName ex T.unpack (humanName ver) escaped (escapeExperiment e) <.> mode | e <- experiments, - ex <- examples, ver <- versions, - mode <- ["svg", "diff.svg","heap.svg"] + mode <- ["svg", "diff.svg"] ++ ["heap.svg" | prof /= NoProfiling] ] +allBinaries :: FilePath -> String -> Action [FilePath] +allBinaries buildFolder executableName = do + versions <- askOracle $ GetVersions () + return $ + [ buildFolder "binaries" T.unpack (humanName ver) executableName + | ver <- versions] + +-- | Generate a set of phony rules: +-- * all +-- * for each example +phonyRules + :: (Traversable t, IsExample e) + => String -- ^ prefix + -> String -- ^ Executable name + -> ProfilingMode + -> FilePath + -> t e + -> Rules () +phonyRules prefix executableName prof buildFolder examples = do + forM_ examples $ \ex -> + phony (prefix <> getExampleName ex) $ need =<< + allTargetsForExample prof buildFolder ex + phony (prefix <> "all") $ do + exampleTargets <- forM examples $ \ex -> + allTargetsForExample prof buildFolder ex + need $ [ buildFolder profilingPath prof "results.csv" ] + ++ concat exampleTargets + phony (prefix <> "all-binaries") $ need =<< allBinaries buildFolder executableName -------------------------------------------------------------------------------- type OutputFolder = FilePath @@ -219,25 +245,47 @@ data BenchProject example = BenchProject , experiment :: Escaped String -- ^ experiment to run } +data ProfilingMode = NoProfiling | CheapHeapProfiling Seconds + deriving (Eq) + +profilingP :: String -> Maybe ProfilingMode +profilingP "unprofiled" = Just NoProfiling +profilingP inp | Just delay <- stripPrefix "profiled-" inp, Just i <- readMaybe delay = Just $ CheapHeapProfiling i +profilingP _ = Nothing + +profilingPath :: ProfilingMode -> FilePath +profilingPath NoProfiling = "unprofiled" +profilingPath (CheapHeapProfiling i) = "profiled-" <> show i + -- TODO generalize BuildSystem -benchRules :: RuleResultForExample example => FilePattern -> Resource -> MkBenchRules BuildSystem example -> Rules () -benchRules build benchResource MkBenchRules{..} = do +benchRules :: RuleResultForExample example => FilePattern -> MkBenchRules BuildSystem example -> Rules () +benchRules build MkBenchRules{..} = do + + benchResource <- newResource "ghcide-bench" 1 -- run an experiment priority 0 $ - [ build -/- "*/*/*.csv", - build -/- "*/*/*.gcStats.log", - build -/- "*/*/*.hp", - build -/- "*/*/*.output.log" - ] - &%> \[outcsv, outGc, outHp, outLog] -> do - let [_, exampleName, ver, exp] = splitDirectories outcsv + [ build -/- "*/*/*/*.csv", + build -/- "*/*/*/*.gcStats.log", + build -/- "*/*/*/*.output.log", + build -/- "*/*/*/*.hp" + ] &%> \[outcsv, outGc, outLog, outHp] -> do + let [_, flavour, exampleName, ver, exp] = splitDirectories outcsv + prof = fromMaybe (error $ "Not a valid profiling mode: " <> flavour) $ profilingP flavour example <- fromMaybe (error $ "Unknown example " <> exampleName) <$> askOracle (GetExample exampleName) buildSystem <- askOracle $ GetBuildSystem () setupRes <- setupProject liftIO $ createDirectoryIfMissing True $ dropFileName outcsv let exePath = build "binaries" ver executableName - exeExtraArgs = ["+RTS", "-h", "-i1", "-qg", "-S" <> outGc, "-RTS"] + exeExtraArgs = + [ "+RTS" + , "-S" <> outGc] + ++ concat + [[ "-h" + , "-i" <> show i + , "-qg"] + | CheapHeapProfiling i <- [prof]] + ++ ["-RTS"] ghcPath = build "binaries" ver "ghc.path" experiment = Escaped $ dropExtension exp need [exePath, ghcPath] @@ -251,7 +299,9 @@ benchRules build benchResource MkBenchRules{..} = do AddPath [takeDirectory ghcPath, "."] [] ] BenchProject {..} - liftIO $ renameFile "ghcide.hp" outHp + liftIO $ case prof of + CheapHeapProfiling{} -> renameFile "ghcide.hp" outHp + NoProfiling -> writeFile outHp dummyHp -- extend csv output with allocation data csvContents <- liftIO $ lines <$> readFile outcsv @@ -265,15 +315,9 @@ benchRules build benchResource MkBenchRules{..} = do let csvContents' = header' : results' writeFileLines outcsv csvContents' where - escapeSpaces :: String -> String - escapeSpaces = map f where - f ' ' = '_' - f x = x - showMB :: Int -> String showMB x = show (x `div` 2^(20::Int)) <> "MB" - -- Parse the max residency and allocations in RTS -s output parseMaxResidencyAndAllocations :: String -> (Int, Int) parseMaxResidencyAndAllocations input = @@ -291,7 +335,7 @@ parseMaxResidencyAndAllocations input = csvRules :: forall example . RuleResultForExample example => FilePattern -> Rules () csvRules build = do -- build results for every experiment*example - build -/- "*/*/results.csv" %> \out -> do + build -/- "*/*/*/results.csv" %> \out -> do experiments <- askOracle $ GetExperiments () let allResultFiles = [takeDirectory out escaped (escapeExperiment e) <.> "csv" | e <- experiments] @@ -302,11 +346,9 @@ csvRules build = do writeFileChanged out $ unlines $ header : concat results -- aggregate all experiments for an example - build -/- "*/results.csv" %> \out -> do + build -/- "*/*/results.csv" %> \out -> do versions <- map (T.unpack . humanName) <$> askOracle (GetVersions ()) - let example = takeFileName $ takeDirectory out - allResultFiles = - [build example v "results.csv" | v <- versions] + let allResultFiles = [takeDirectory out v "results.csv" | v <- versions] allResults <- traverse readFileLines allResultFiles @@ -318,9 +360,9 @@ csvRules build = do writeFileChanged out $ unlines $ header' : interleave results' -- aggregate all examples - build -/- "results.csv" %> \out -> do + build -/- "*/results.csv" %> \out -> do examples <- map (getExampleName @example) <$> askOracle (GetExamples ()) - let allResultFiles = [build e "results.csv" | e <- examples] + let allResultFiles = [takeDirectory out e "results.csv" | e <- examples] allResults <- traverse readFileLines allResultFiles @@ -336,40 +378,38 @@ csvRules build = do -- | Rules to produce charts for the GC stats svgRules :: FilePattern -> Rules () svgRules build = do - - _ <- addOracle $ \(GetParent name) -> findPrev name <$> askOracle (GetVersions ()) - + void $ addOracle $ \(GetParent name) -> findPrev name <$> askOracle (GetVersions ()) -- chart GC stats for an experiment on a given revision priority 1 $ - build -/- "*/*/*.svg" %> \out -> do - let [b, example, ver, exp] = splitDirectories out - runLog <- loadRunLog b example (Escaped $ dropExtension exp) ver + build -/- "*/*/*/*.svg" %> \out -> do + let [_, _, _example, ver, _exp] = splitDirectories out + runLog <- loadRunLog (Escaped $ replaceExtension out "csv") ver let diagram = Diagram Live [runLog] title title = ver <> " live bytes over time" plotDiagram True diagram out -- chart of GC stats for an experiment on this and the previous revision priority 2 $ - build -/- "*/*/*.diff.svg" %> \out -> do - let [b, example, ver, exp_] = splitDirectories out - exp = Escaped $ dropExtension $ dropExtension exp_ - prev <- askOracle $ GetParent $ T.pack ver + build -/- "*/*/*/*.diff.svg" %> \out -> do + let [b, flav, example, ver, exp_] = splitDirectories out + exp = Escaped $ dropExtension2 exp_ + prev <- fmap T.unpack $ askOracle $ GetParent $ T.pack ver - runLog <- loadRunLog b example exp ver - runLogPrev <- loadRunLog b example exp $ T.unpack prev + runLog <- loadRunLog (Escaped $ replaceExtension (dropExtension out) "csv") ver + runLogPrev <- loadRunLog (Escaped $ joinPath [b,flav, example, prev, replaceExtension (dropExtension exp_) "csv"]) prev let diagram = Diagram Live [runLog, runLogPrev] title title = show (unescapeExperiment exp) <> " - live bytes over time compared" plotDiagram True diagram out -- aggregated chart of GC stats for all the revisions - build -/- "*/*.svg" %> \out -> do + build -/- "*/*/*.svg" %> \out -> do let exp = Escaped $ dropExtension $ takeFileName out - example = takeFileName $ takeDirectory out versions <- askOracle $ GetVersions () runLogs <- forM (filter include versions) $ \v -> do - loadRunLog build example exp $ T.unpack $ humanName v + let v' = T.unpack (humanName v) + loadRunLog (Escaped $ takeDirectory out v' replaceExtension (takeFileName out) "csv") v' let diagram = Diagram Live runLogs title title = show (unescapeExperiment exp) <> " - live bytes over time" @@ -378,12 +418,14 @@ svgRules build = do heapProfileRules :: FilePattern -> Rules () heapProfileRules build = do priority 3 $ - build -/- "*/*/*.heap.svg" %> \out -> do - let hpFile = dropExtension (dropExtension out) <.> "hp" + build -/- "*/*/*/*.heap.svg" %> \out -> do + let hpFile = dropExtension2 out <.> "hp" need [hpFile] cmd_ ("hp2pretty" :: String) [hpFile] liftIO $ renameFile (dropExtension hpFile <.> "svg") out +dropExtension2 :: FilePath -> FilePath +dropExtension2 = dropExtension . dropExtension -------------------------------------------------------------------------------- -------------------------------------------------------------------------------- @@ -482,16 +524,13 @@ instance Read Frame where -- | A file path containing the output of -S for a given run data RunLog = RunLog { runVersion :: !String, - _runExample :: !String, - _runExperiment :: !String, runFrames :: ![Frame], runSuccess :: !Bool } -loadRunLog :: HasCallStack => FilePath -> String -> Escaped FilePath -> FilePath -> Action RunLog -loadRunLog buildF example exp ver = do - let csv_fp = buildF example ver escaped exp <.> "csv" - log_fp = replaceExtension csv_fp "gcStats.log" +loadRunLog :: HasCallStack => Escaped FilePath -> String -> Action RunLog +loadRunLog (Escaped csv_fp) ver = do + let log_fp = replaceExtension csv_fp "gcStats.log" log <- readFileLines log_fp csv <- readFileLines csv_fp let frames = @@ -505,7 +544,7 @@ loadRunLog buildF example exp ver = do success = case map (T.split (== ',') . T.pack) csv of [_header, _name:s:_] | Just s <- readMaybe (T.unpack s) -> s _ -> error $ "Cannot parse: " <> csv_fp - return $ RunLog ver example (dropExtension $ escaped exp) frames success + return $ RunLog ver frames success -------------------------------------------------------------------------------- @@ -618,3 +657,12 @@ myColors = map E.opaque , E.sienna , E.peru ] + +dummyHp :: String +dummyHp = + "JOB \"ghcide\" \ + \DATE \"Sun Jan 31 09:30 2021\" \ + \SAMPLE_UNIT \"seconds\" \ + \VALUE_UNIT \"bytes\" \ + \BEGIN_SAMPLE 0.000000 \ + \END_SAMPLE 0.000000"