Andreas Klebinger pushed to branch wip/andreask/bomb_out at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Core/Unfold.hs
    ... ... @@ -335,6 +335,7 @@ isValFun (Lam b e) | isRuntimeVar b = True
    335 335
                        | otherwise      = isValFun e
    
    336 336
     isValFun _                          = False
    
    337 337
     
    
    338
    +{-# NOINLINE calcUnfoldingGuidance #-}
    
    338 339
     calcUnfoldingGuidance
    
    339 340
             :: UnfoldingOpts
    
    340 341
             -> Bool          -- Definitely a top-level, bottoming binding
    
    ... ... @@ -566,44 +567,48 @@ sizeExpr :: UnfoldingOpts
    566 567
     
    
    567 568
     -- Forcing bOMB_OUT_SIZE early prevents repeated
    
    568 569
     -- unboxing of the Int argument.
    
    570
    +-- {-# NOINLINE sizeExpr #-}
    
    569 571
     sizeExpr opts !bOMB_OUT_SIZE top_args expr
    
    570
    -  = size_up expr
    
    572
    +  = size_up sizeZero expr
    
    571 573
       where
    
    572
    -    size_up (Cast e _) = size_up e
    
    573
    -    size_up (Tick _ e) = size_up e
    
    574
    -    size_up (Type _)   = sizeZero           -- Types cost nothing
    
    575
    -    size_up (Coercion _) = sizeZero
    
    576
    -    size_up (Lit lit)  = sizeN (litSize lit)
    
    577
    -    size_up (Var f) | isZeroBitId f = sizeZero
    
    578
    -                      -- Make sure we get constructor discounts even
    
    579
    -                      -- on nullary constructors
    
    580
    -                    | otherwise       = size_up_call f [] 0
    
    581
    -
    
    582
    -    size_up (App fun arg)
    
    583
    -      | isTyCoArg arg = size_up fun
    
    584
    -      | otherwise     = size_up arg  `addSizeNSD`
    
    585
    -                        size_up_app fun [arg] (if isZeroBitExpr arg then 1 else 0)
    
    586
    -
    
    587
    -    size_up (Lam b e)
    
    588
    -      | isId b && not (isZeroBitId b) = lamScrutDiscount opts (size_up e `addSizeN` 10)
    
    589
    -      | otherwise = size_up e
    
    590
    -
    
    591
    -    size_up (Let (NonRec binder rhs) body)
    
    592
    -      = size_up_rhs (binder, rhs) `addSizeNSD`
    
    593
    -        size_up body              `addSizeN`
    
    594
    -        size_up_alloc binder
    
    595
    -
    
    596
    -    size_up (Let (Rec pairs) body)
    
    597
    -      = foldr (addSizeNSD . size_up_rhs)
    
    598
    -              (size_up body `addSizeN` sum (map (size_up_alloc . fst) pairs))
    
    599
    -              pairs
    
    600
    -
    
    601
    -    size_up (Case e _ _ alts) = case nonEmpty alts of
    
    602
    -      Nothing -> size_up e    -- case e of {} never returns, so take size of scrutinee
    
    574
    +    size_up :: ExprSize -> CoreExpr -> ExprSize
    
    575
    +    size_up (TooBig) !_ = TooBig
    
    576
    +    size_up (SizeIs !s _ _) _
    
    577
    +      | s > bOMB_OUT_SIZE = TooBig
    
    578
    +    size_up s (Cast e _)  = size_up s e
    
    579
    +    size_up s (Tick _ e)  = size_up s e
    
    580
    +    size_up s (Type _)    = s           -- Types cost nothing
    
    581
    +    size_up s (Coercion _)  = s
    
    582
    +    size_up s (Lit lit)  = addSizeNSD (sizeN (litSize lit)) s
    
    583
    +    size_up s (Var f)    | isZeroBitId f = s
    
    584
    +                        -- Make sure we get constructor discounts even
    
    585
    +                        -- on nullary constructors
    
    586
    +                        | otherwise       = size_up_call s f [] 0
    
    587
    +
    
    588
    +    size_up s (App fun arg)
    
    589
    +      | isTyCoArg arg = size_up s fun
    
    590
    +      | otherwise     =  size_up_app (stripDiscounts $ size_up s arg)
    
    591
    +                                     fun [arg] (if isZeroBitExpr arg then 1 else 0)
    
    592
    +
    
    593
    +    size_up s (Lam b e)
    
    594
    +      | isId b && not (isZeroBitId b) = lamScrutDiscount opts (size_up (addSizeN s 10) e)
    
    595
    +      | otherwise = size_up s e
    
    596
    +
    
    597
    +    size_up s (Let (NonRec binder rhs) body)
    
    598
    +      = let rhs_s = size_up_let s (binder, rhs)
    
    599
    +        in size_up (stripDiscounts $ rhs_s) body
    
    600
    +
    
    601
    +
    
    602
    +    size_up s (Let (Rec pairs) body)
    
    603
    +      = size_up (stripDiscounts (foldr (flip size_up_let) s pairs))
    
    604
    +                body
    
    605
    +
    
    606
    +    size_up s (Case e _ _ alts) = case nonEmpty alts of
    
    607
    +      Nothing -> size_up s e    -- case e of {} never returns, so take size of scrutinee
    
    603 608
           Just alts
    
    604 609
             | Just v <- is_top_arg e -> -- We are scrutinising an argument variable
    
    605 610
               let
    
    606
    -            alt_sizes = NE.map size_up_alt alts
    
    611
    +            alt_sizes = NE.map (size_up_alt s) alts
    
    607 612
     
    
    608 613
                       -- alts_size tries to compute a good discount for
    
    609 614
                       -- the case when we are scrutinising an argument variable
    
    ... ... @@ -625,21 +630,24 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr
    625 630
     
    
    626 631
                 alts_size tot_size _ = tot_size
    
    627 632
               in
    
    628
    -          alts_size (foldr1 addAltSize alt_sizes)  -- alts is non-empty
    
    629
    -                    (foldr1 maxSize    alt_sizes)
    
    633
    +          s `addSizeNSD`  alts_size (foldr1 addAltSize alt_sizes)  -- alts is non-empty
    
    634
    +                                    (foldr1 maxSize    alt_sizes)
    
    630 635
                     -- Good to inline if an arg is scrutinised, because
    
    631 636
                     -- that may eliminate allocation in the caller
    
    632 637
                     -- And it eliminates the case itself
    
    633 638
     
    
    634
    -        | otherwise -> size_up e  `addSizeNSD`
    
    635
    -                                foldr (addAltSize . size_up_alt) case_size alts
    
    639
    +        | otherwise -> foldr  (addAltSize . size_up_alt s)
    
    640
    +                              (size_up s e  `addSizeNSD` case_size)
    
    641
    +                              alts
    
    636 642
     
    
    637 643
             where
    
    638 644
               is_top_arg (Var v) | v `elem` top_args = Just v
    
    639 645
               is_top_arg (Cast e _) = is_top_arg e
    
    646
    +          is_top_arg (Tick _t e) = is_top_arg e
    
    640 647
               is_top_arg _ = Nothing
    
    641 648
     
    
    642 649
           where
    
    650
    +
    
    643 651
               case_size
    
    644 652
                | is_inline_scrut e, lengthAtMost alts 1 = sizeN (-10)
    
    645 653
                | otherwise = sizeZero
    
    ... ... @@ -675,48 +683,61 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr
    675 683
                   | otherwise
    
    676 684
                     = False
    
    677 685
     
    
    678
    -    size_up_rhs (bndr, rhs)
    
    686
    +    size_up_let :: ExprSize -> (Id, CoreExpr) -> ExprSize
    
    687
    +    size_up_let s (bndr, rhs)
    
    679 688
           | JoinPoint join_arity <- idJoinPointHood bndr
    
    680 689
             -- Skip arguments to join point
    
    681 690
           , (_bndrs, body) <- collectNBinders join_arity rhs
    
    682
    -      = size_up body
    
    691
    +      = size_up s body
    
    683 692
           | otherwise
    
    684
    -      = size_up rhs
    
    693
    +      = size_up s rhs `addSizeN` size_up_alloc bndr
    
    685 694
     
    
    686 695
         ------------
    
    687 696
         -- size_up_app is used when there's ONE OR MORE value args
    
    688
    -    size_up_app (App fun arg) args voids
    
    689
    -        | isTyCoArg arg                  = size_up_app fun args voids
    
    690
    -        | isZeroBitExpr arg              = size_up_app fun (arg:args) (voids + 1)
    
    691
    -        | otherwise                      = size_up arg  `addSizeNSD`
    
    692
    -                                           size_up_app fun (arg:args) voids
    
    693
    -    size_up_app (Var fun)     args voids = size_up_call fun args voids
    
    694
    -    size_up_app (Tick _ expr) args voids = size_up_app expr args voids
    
    695
    -    size_up_app (Cast expr _) args voids = size_up_app expr args voids
    
    696
    -    size_up_app other         args voids = size_up other `addSizeN`
    
    697
    -                                           callSize (length args) voids
    
    697
    +    size_up_app :: ExprSize -> CoreExpr -> [CoreExpr] -> Int -> ExprSize
    
    698
    +    size_up_app s (App fun arg) args voids
    
    699
    +        | isTyCoArg arg                  = size_up_app s fun args voids
    
    700
    +        | isZeroBitExpr arg              = size_up_app s fun (arg:args) (voids + 1)
    
    701
    +        | otherwise                      =  let arg_size = stripDiscounts $ size_up s arg
    
    702
    +                                            in size_up_app arg_size fun (arg:args) voids
    
    703
    +    size_up_app s (Var fun)     args voids = size_up_call s fun args voids
    
    704
    +    size_up_app s (Tick _ expr) args voids = size_up_app s expr args voids
    
    705
    +    size_up_app s (Cast expr _) args voids = size_up_app s expr args voids
    
    706
    +    size_up_app s other         args voids = size_up (s `addSizeN` callSize (length args) voids) other
    
    707
    +
    
    698 708
            -- if the lhs is not an App or a Var, or an invisible thing like a
    
    699 709
            -- Tick or Cast, then we should charge for a complete call plus the
    
    700 710
            -- size of the lhs itself.
    
    701 711
     
    
    702 712
         ------------
    
    703
    -    size_up_call :: Id -> [CoreExpr] -> Int -> ExprSize
    
    704
    -    size_up_call fun val_args voids
    
    705
    -       = case idDetails fun of
    
    706
    -           FCallId _                     -> sizeN (callSize (length val_args) voids)
    
    707
    -           DataConWorkId dc              -> conSize    dc (length val_args)
    
    708
    -           PrimOpId op _                 -> primOpSize op (length val_args)
    
    709
    -           ClassOpId cls _               -> classOpSize opts cls top_args val_args
    
    710
    -           _ | fun `hasKey` buildIdKey   -> buildSize
    
    711
    -             | fun `hasKey` augmentIdKey -> augmentSize
    
    712
    -             | otherwise                 -> funSize opts top_args fun (length val_args) voids
    
    713
    +    size_up_call :: ExprSize -> Id -> [CoreExpr] -> Int -> ExprSize
    
    714
    +    size_up_call !s fun val_args voids
    
    715
    +       = let !n_args = length val_args
    
    716
    +             call_size = case idDetails fun of
    
    717
    +                            FCallId _                     -> sizeN (callSize n_args voids)
    
    718
    +                            DataConWorkId dc              -> conSize    dc n_args
    
    719
    +                            PrimOpId op _                 -> primOpSize op n_args
    
    720
    +                            ClassOpId cls _               -> classOpSize opts cls top_args val_args
    
    721
    +                            _ | fun `hasKey` buildIdKey   -> buildSize
    
    722
    +                              | fun `hasKey` augmentIdKey -> augmentSize
    
    723
    +                              | otherwise                 -> funSize opts top_args fun n_args voids
    
    724
    +          in s `addSizeNSD` call_size
    
    713 725
     
    
    714 726
         ------------
    
    715
    -    size_up_alt (Alt _con _bndrs rhs) = size_up rhs `addSizeN` 10
    
    727
    +    -- size_up_alt returns on the alternatives size, not counting the accumulated
    
    728
    +    -- size passed in unless we reach TooBig. This is to facility better discount
    
    729
    +    -- calculation based on the size of only the alternative.
    
    730
    +    size_up_alt TooBig _ = TooBig
    
    731
    +    size_up_alt (SizeIs {_es_size_is=s}) (Alt _con _bndrs rhs) =
    
    732
    +        size_up (sizeN s) rhs
    
    733
    +                -- Why add and then subtract s?
    
    734
    +                -- If the expression large enough this will ensure we bomb out early.
    
    735
    +                `addSizeN` (10 -s)
    
    736
    +
    
    716 737
             -- Don't charge for args, so that wrappers look cheap
    
    717 738
             -- (See comments about wrappers with Case)
    
    718 739
             --
    
    719
    -        -- IMPORTANT: *do* charge 1 for the alternative, else we
    
    740
    +        -- IMPORTANT: *do* charge 10 for the alternative, else we
    
    720 741
             -- find that giant case nests are treated as practically free
    
    721 742
             -- A good example is Foreign.C.Error.errnoToIOError
    
    722 743
     
    
    ... ... @@ -753,6 +774,14 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr
    753 774
                                      (xs `unionBags` ys)
    
    754 775
                                      d2  -- Ignore d1
    
    755 776
     
    
    777
    +    -- Throw away the discount for scrutinizing the expression.
    
    778
    +    -- Used for things like `let x = rhs in body` where we only consider
    
    779
    +    -- this benefit for the body.
    
    780
    +    -- Why? `x` is visible to `body` either way, so it really should not
    
    781
    +    -- affect our inlining decision either way.
    
    782
    +    stripDiscounts TooBig = TooBig
    
    783
    +    stripDiscounts (SizeIs n xs _) = (SizeIs n xs 0)
    
    784
    +
    
    756 785
         -- don't count expressions such as State# RealWorld
    
    757 786
         -- exclude join points, because they can be rep-polymorphic
    
    758 787
         -- and typePrimRep will crash