[Git][ghc/ghc][wip/andreask/bomb_out] exprSize: Accumulate size as we go to allow early bomb out.
Andreas Klebinger pushed to branch wip/andreask/bomb_out at Glasgow Haskell Compiler / GHC Commits: 76d7a6ad by Andreas Klebinger at 2025-09-24T19:54:36+02:00 exprSize: Accumulate size as we go to allow early bomb out. - - - - - 2 changed files: - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Unfold.hs Changes: ===================================== compiler/GHC/Core/Opt/OccurAnal.hs ===================================== @@ -2,7 +2,9 @@ {-# OPTIONS_GHC -cpp -Wno-incomplete-record-updates #-} -{-# OPTIONS_GHC -fmax-worker-args=12 #-} +{-# OPTIONS_GHC -fmax-worker-args=12 -fprof-late #-} + +{-# OPTIONS_GHC -dumpdir dumps -ddump-to-file -ddump-simpl #-} -- The -fmax-worker-args=12 is there because the main functions -- are strict in the OccEnv, and it turned out that with the default settting -- some functions would unbox the OccEnv ad some would not, depending on how ===================================== compiler/GHC/Core/Unfold.hs ===================================== @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dumpdir dumps #-} + {- (c) The University of Glasgow 2006 (c) The AQUA Project, Glasgow University, 1994-1998 @@ -335,6 +337,7 @@ isValFun (Lam b e) | isRuntimeVar b = True | otherwise = isValFun e isValFun _ = False +{-# NOINLINE calcUnfoldingGuidance #-} calcUnfoldingGuidance :: UnfoldingOpts -> Bool -- Definitely a top-level, bottoming binding @@ -567,43 +570,43 @@ sizeExpr :: UnfoldingOpts -- Forcing bOMB_OUT_SIZE early prevents repeated -- unboxing of the Int argument. sizeExpr opts !bOMB_OUT_SIZE top_args expr - = size_up expr + = size_up sizeZero expr where - size_up (Cast e _) = size_up e - size_up (Tick _ e) = size_up e - size_up (Type _) = sizeZero -- Types cost nothing - size_up (Coercion _) = sizeZero - size_up (Lit lit) = sizeN (litSize lit) - size_up (Var f) | isZeroBitId f = sizeZero - -- Make sure we get constructor discounts even - -- on nullary constructors - | otherwise = size_up_call f [] 0 - - size_up (App fun arg) - | isTyCoArg arg = size_up fun - | otherwise = size_up arg `addSizeNSD` - size_up_app fun [arg] (if isZeroBitExpr arg then 1 else 0) - - size_up (Lam b e) - | isId b && not (isZeroBitId b) = lamScrutDiscount opts (size_up e `addSizeN` 10) - | otherwise = size_up e - - size_up (Let (NonRec binder rhs) body) - = size_up_rhs (binder, rhs) `addSizeNSD` - size_up body `addSizeN` - size_up_alloc binder - - size_up (Let (Rec pairs) body) - = foldr (addSizeNSD . size_up_rhs) - (size_up body `addSizeN` sum (map (size_up_alloc . fst) pairs)) - pairs - - size_up (Case e _ _ alts) = case nonEmpty alts of - Nothing -> size_up e -- case e of {} never returns, so take size of scrutinee + size_up :: ExprSize -> CoreExpr -> ExprSize + size_up s (Cast e _) = size_up s e + size_up s (Tick _ e) = size_up s e + size_up s (Type _) = s -- Types cost nothing + size_up s (Coercion _) = s + size_up s (Lit lit) = addSizeNSD (sizeN (litSize lit)) s + size_up s (Var f) | isZeroBitId f = s + -- Make sure we get constructor discounts even + -- on nullary constructors + | otherwise = size_up_call s f [] 0 + + size_up s (App fun arg) + | isTyCoArg arg = size_up s fun + | otherwise = size_up_app (stripDiscounts $ size_up s arg) + fun [arg] (if isZeroBitExpr arg then 1 else 0) + + size_up s (Lam b e) + | isId b && not (isZeroBitId b) = lamScrutDiscount opts (size_up (addSizeN s 10) e) + | otherwise = size_up s e + + size_up s (Let (NonRec binder rhs) body) + = let rhs_s = size_up_rhs s (binder, rhs) + in size_up (stripDiscounts $ rhs_s `addSizeN` size_up_alloc binder) body + + + size_up s (Let (Rec pairs) body) + = size_up (stripDiscounts (foldr (flip size_up_rhs) s pairs)) + body + + size_up s (Case e _ _ alts) = case nonEmpty alts of + Nothing -> size_up s e -- case e of {} never returns, so take size of scrutinee Just alts | Just v <- is_top_arg e -> -- We are scrutinising an argument variable let - alt_sizes = NE.map size_up_alt alts + alt_sizes = NE.map (size_up_alt s) alts -- alts_size tries to compute a good discount for -- the case when we are scrutinising an argument variable @@ -625,18 +628,19 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr alts_size tot_size _ = tot_size in - alts_size (foldr1 addAltSize alt_sizes) -- alts is non-empty - (foldr1 maxSize alt_sizes) + s `addSizeNSD` alts_size (foldr1 addAltSize alt_sizes) -- alts is non-empty + (foldr1 maxSize alt_sizes) -- Good to inline if an arg is scrutinised, because -- that may eliminate allocation in the caller -- And it eliminates the case itself - | otherwise -> size_up e `addSizeNSD` - foldr (addAltSize . size_up_alt) case_size alts + | otherwise -> let case_s = size_up s e `addSizeNSD` case_size + in foldr (addAltSize . size_up_alt case_s) case_s alts where is_top_arg (Var v) | v `elem` top_args = Just v is_top_arg (Cast e _) = is_top_arg e + is_top_arg (Tick _t e) = is_top_arg e is_top_arg _ = Nothing where @@ -675,44 +679,52 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr | otherwise = False - size_up_rhs (bndr, rhs) + size_up_rhs :: ExprSize -> (Id, CoreExpr) -> ExprSize + size_up_rhs s (bndr, rhs) | JoinPoint join_arity <- idJoinPointHood bndr -- Skip arguments to join point , (_bndrs, body) <- collectNBinders join_arity rhs - = size_up body + = size_up s body | otherwise - = size_up rhs + = size_up s rhs ------------ -- size_up_app is used when there's ONE OR MORE value args - size_up_app (App fun arg) args voids - | isTyCoArg arg = size_up_app fun args voids - | isZeroBitExpr arg = size_up_app fun (arg:args) (voids + 1) - | otherwise = size_up arg `addSizeNSD` - size_up_app fun (arg:args) voids - size_up_app (Var fun) args voids = size_up_call fun args voids - size_up_app (Tick _ expr) args voids = size_up_app expr args voids - size_up_app (Cast expr _) args voids = size_up_app expr args voids - size_up_app other args voids = size_up other `addSizeN` - callSize (length args) voids + size_up_app :: ExprSize -> CoreExpr -> [CoreExpr] -> Int -> ExprSize + size_up_app s (App fun arg) args voids + | isTyCoArg arg = size_up_app s fun args voids + | isZeroBitExpr arg = size_up_app s fun (arg:args) (voids + 1) + | otherwise = let arg_size = stripDiscounts $ size_up s arg + in size_up_app arg_size fun (arg:args) voids + size_up_app s (Var fun) args voids = size_up_call s fun args voids + size_up_app s (Tick _ expr) args voids = size_up_app s expr args voids + size_up_app s (Cast expr _) args voids = size_up_app s expr args voids + size_up_app s other args voids = size_up (s `addSizeN` callSize (length args) voids) other + -- if the lhs is not an App or a Var, or an invisible thing like a -- Tick or Cast, then we should charge for a complete call plus the -- size of the lhs itself. ------------ - size_up_call :: Id -> [CoreExpr] -> Int -> ExprSize - size_up_call fun val_args voids - = case idDetails fun of - FCallId _ -> sizeN (callSize (length val_args) voids) - DataConWorkId dc -> conSize dc (length val_args) - PrimOpId op _ -> primOpSize op (length val_args) - ClassOpId cls _ -> classOpSize opts cls top_args val_args - _ | fun `hasKey` buildIdKey -> buildSize - | fun `hasKey` augmentIdKey -> augmentSize - | otherwise -> funSize opts top_args fun (length val_args) voids + size_up_call :: ExprSize -> Id -> [CoreExpr] -> Int -> ExprSize + size_up_call s fun val_args voids + = let call_size = case idDetails fun of + FCallId _ -> sizeN (callSize (length val_args) voids) + DataConWorkId dc -> conSize dc (length val_args) + PrimOpId op _ -> primOpSize op (length val_args) + ClassOpId cls _ -> classOpSize opts cls top_args val_args + _ | fun `hasKey` buildIdKey -> buildSize + | fun `hasKey` augmentIdKey -> augmentSize + | otherwise -> funSize opts top_args fun (length val_args) voids + in s `addSizeNSD` call_size ------------ - size_up_alt (Alt _con _bndrs rhs) = size_up rhs `addSizeN` 10 + -- size_up_alt returns on the alternatives size, not including the accumulated size passed in unless we reach TooBig + size_up_alt TooBig _ = TooBig + size_up_alt (SizeIs {_es_size_is=s}) (Alt _con _bndrs rhs) = + size_up (sizeN $ s + 10) rhs + `addSizeN` (-s) -- Why add and then subtract s? If the expression is already large we will bomb out early this way. + -- Don't charge for args, so that wrappers look cheap -- (See comments about wrappers with Case) -- @@ -753,6 +765,9 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr (xs `unionBags` ys) d2 -- Ignore d1 + stripDiscounts TooBig = TooBig + stripDiscounts (SizeIs n xs _) = (SizeIs n xs 0) + -- don't count expressions such as State# RealWorld -- exclude join points, because they can be rep-polymorphic -- and typePrimRep will crash View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/76d7a6adeee40491157a2f90aa70c11b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/76d7a6adeee40491157a2f90aa70c11b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Andreas Klebinger (@AndreasK)