Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/CmmToAsm/Reg/Linear.hs
    ... ... @@ -406,7 +406,7 @@ linearRA block_live block_id = go [] []
    406 406
     -- | Do allocation for a single instruction.
    
    407 407
     raInsn
    
    408 408
             :: OutputableRegConstraint freeRegs instr
    
    409
    -        => BlockMap Regs                      -- ^ map of what vregs are love on entry to each block.
    
    409
    +        => BlockMap Regs                         -- ^ map of what vregs are live on entry to each block.
    
    410 410
             -> [instr]                              -- ^ accumulator for instructions already processed.
    
    411 411
             -> BlockId                              -- ^ the id of the current block, for debugging
    
    412 412
             -> LiveInstr instr                      -- ^ the instr to have its regs allocated, with liveness info.
    

  • compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs
    ... ... @@ -37,7 +37,11 @@ data StackMap
    37 37
     
    
    38 38
               -- See Note [UniqFM and the register allocator]
    
    39 39
               -- | Assignment of vregs to stack slots.
    
    40
    -        , stackMapAssignment    :: UniqFM Unique StackSlot }
    
    40
    +          --
    
    41
    +          -- We record not just the slot, but also how many stack slots the vreg
    
    42
    +          -- takes up, in order to avoid re-using a stack slot for a register
    
    43
    +          -- that has grown but already had a stack slot (#26668).
    
    44
    +        , stackMapAssignment    :: UniqFM Unique (StackSlot, Int) }
    
    41 45
     
    
    42 46
     
    
    43 47
     -- | An empty stack map, with all slots available.
    
    ... ... @@ -50,14 +54,19 @@ emptyStackMap = StackMap 0 emptyUFM
    50 54
     --
    
    51 55
     getStackSlotFor :: StackMap -> Format -> Unique -> (StackMap, Int)
    
    52 56
     
    
    53
    -getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique
    
    54
    -  | Just slot <- lookupUFM reserved regUnique  =  (fs, slot)
    
    55
    -
    
    56
    -getStackSlotFor (StackMap freeSlot reserved) fmt regUnique =
    
    57
    -  let
    
    58
    -    nbSlots = (formatInBytes fmt + 7) `div` 8
    
    59
    -  in
    
    60
    -    (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot)
    
    57
    +getStackSlotFor fs@(StackMap freeSlot reserved) fmt regUnique
    
    58
    +  -- The register already has a stack slot; try to re-use it.
    
    59
    +  | Just (slot, nbSlots) <- lookupUFM reserved regUnique
    
    60
    +  -- Make sure the slot is big enough for this format, in case the register
    
    61
    +  -- has grown (#26668).
    
    62
    +  , nbNeededSlots <= nbSlots
    
    63
    +  = (fs, slot)
    
    64
    +  | otherwise
    
    65
    +  = (StackMap (freeSlot+nbNeededSlots) (addToUFM reserved regUnique (freeSlot, nbNeededSlots)), freeSlot)
    
    66
    +    -- NB: this can create fragmentation if a register keeps growing.
    
    67
    +    -- That's probably OK, as this is only happens very rarely.
    
    68
    +  where
    
    69
    +    !nbNeededSlots = (formatInBytes fmt + 7) `div` 8
    
    61 70
     
    
    62 71
     -- | Return the number of stack slots that were allocated
    
    63 72
     getStackUse :: StackMap -> Int