Skip to content
Snippets Groups Projects
Commit 88a94541 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Hadrian: avoid useless allocations in trackArgument

Cf ticky report before the change:

    Entries      Alloc    Alloc'd  Non-void Arguments      STG Name
--------------------------------------------------------------------------------
     696987   29044128          0   1 L                    main:Target.trackArgument_go5{v r24kY} (fun)
parent 7fe07143
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE LambdaCase #-}
module Target ( module Target (
Target, target, context, builder, inputs, outputs, trackArgument, Target, target, context, builder, inputs, outputs, trackArgument,
module Builder module Builder
...@@ -25,8 +27,14 @@ trackArgument target arg = case builder target of ...@@ -25,8 +27,14 @@ trackArgument target arg = case builder target of
Cabal _ _ -> not $ verbosityArg arg || cabal_configure_ignore arg Cabal _ _ -> not $ verbosityArg arg || cabal_configure_ignore arg
_ -> True _ -> True
where where
threadArg s = dropWhileEnd isDigit s `elem` ["-j", "MAKEFLAGS=-j", "THREADS="] match_str_num [] rs = all isDigit rs
verbosityArg s = dropWhileEnd isDigit s == "-v" match_str_num (x:xs) (r:rs) = x == r && match_str_num xs rs
match_str_num (_:_) [] = False
threadArg s = match_str_num "-j" s || match_str_num "MAKEFLAGS=-j" s || match_str_num "THREADS=" s
verbosityArg s = match_str_num "-v" s
diagnosticsColorArg s = "-fdiagnostics-color=" `isPrefixOf` s -- N.B. #18672 diagnosticsColorArg s = "-fdiagnostics-color=" `isPrefixOf` s -- N.B. #18672
cabal_configure_ignore s = cabal_configure_ignore = \case
s `elem` [ "--configure-option=--quiet", "--configure-option=--disable-option-checking" ] "--configure-option=--quiet" -> True
"--configure-option=--disable-option-checking" -> True
_ -> False
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment