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

Commits:

1 changed file:

Changes:

  • compiler/GHC/Runtime/Debugger/Breakpoints.hs
    ... ... @@ -11,7 +11,7 @@ import Control.Monad.Catch
    11 11
     import Control.Monad
    
    12 12
     import Data.Array
    
    13 13
     import Data.Function
    
    14
    -import Data.List
    
    14
    +import qualified Data.List as List
    
    15 15
     import Data.Maybe
    
    16 16
     import qualified Data.List.NonEmpty as NE
    
    17 17
     import qualified Data.Semigroup as S
    
    ... ... @@ -51,16 +51,16 @@ findBreakByLine :: Int {-^ Line number -} -> TickArray -> Maybe (BreakTickIndex,
    51 51
     findBreakByLine line arr
    
    52 52
       | not (inRange (bounds arr) line) = Nothing
    
    53 53
       | otherwise =
    
    54
    -    listToMaybe (sortBy (leftmostLargestRealSrcSpan `on` snd)  comp)   `mplus`
    
    55
    -    listToMaybe (sortBy (compare `on` snd) incomp) `mplus`
    
    56
    -    listToMaybe (sortBy (flip compare `on` snd) ticks)
    
    54
    +    listToMaybe (List.sortBy (leftmostLargestRealSrcSpan `on` snd)  comp)   `mplus`
    
    55
    +    listToMaybe (List.sortBy (compare `on` snd) incomp) `mplus`
    
    56
    +    listToMaybe (List.sortBy (flip compare `on` snd) ticks)
    
    57 57
       where
    
    58 58
             ticks = arr ! line
    
    59 59
     
    
    60 60
             starts_here = [ (ix,pan) | (ix, pan) <- ticks,
    
    61 61
                             srcSpanStartLine pan == line ]
    
    62 62
     
    
    63
    -        (comp, incomp) = partition ends_here starts_here
    
    63
    +        (comp, incomp) = List.partition ends_here starts_here
    
    64 64
                 where ends_here (_,pan) = srcSpanEndLine pan == line
    
    65 65
     
    
    66 66
     -- | Find a breakpoint in the 'TickArray' of a module, given a line number and a column coordinate.
    
    ... ... @@ -68,8 +68,8 @@ findBreakByCoord :: (Int, Int) -> TickArray -> Maybe (BreakTickIndex, RealSrcSpa
    68 68
     findBreakByCoord (line, col) arr
    
    69 69
       | not (inRange (bounds arr) line) = Nothing
    
    70 70
       | otherwise =
    
    71
    -    listToMaybe (sortBy (flip compare `on` snd) contains ++
    
    72
    -                 sortBy (compare `on` snd) after_here)
    
    71
    +    listToMaybe (List.sortBy (flip compare `on` snd) contains ++
    
    72
    +                 List.sortBy (compare `on` snd) after_here)
    
    73 73
       where
    
    74 74
             ticks = arr ! line
    
    75 75
     
    
    ... ... @@ -88,7 +88,7 @@ enclosingTickSpan :: TickArray -> SrcSpan -> RealSrcSpan
    88 88
     enclosingTickSpan _ (UnhelpfulSpan _) = panic "enclosingTickSpan UnhelpfulSpan"
    
    89 89
     enclosingTickSpan ticks (RealSrcSpan src _) =
    
    90 90
       assert (inRange (bounds ticks) line) $
    
    91
    -    Data.List.minimumBy leftmostLargestRealSrcSpan $ enclosing_spans
    
    91
    +    List.minimumBy leftmostLargestRealSrcSpan $ enclosing_spans
    
    92 92
       where
    
    93 93
         line = srcSpanStartLine src
    
    94 94
         enclosing_spans = [ pan | (_,pan) <- ticks ! line
    
    ... ... @@ -144,7 +144,7 @@ resolveFunctionBreakpoint inp = do
    144 144
         lookupModuleInGraph mod_str = do
    
    145 145
             graph <- getModuleGraph
    
    146 146
             let hmods = ms_mod <$> mgModSummaries graph
    
    147
    -        pure $ find ((== mod_str) . moduleNameString . moduleName) hmods
    
    147
    +        pure $ List.find ((== mod_str) . moduleNameString . moduleName) hmods
    
    148 148
     
    
    149 149
         -- Check validity of an identifier to set a breakpoint:
    
    150 150
         --  1. The module of the identifier must exist
    
    ... ... @@ -165,7 +165,7 @@ resolveFunctionBreakpoint inp = do
    165 165
                 mb_modbreaks <- getModBreak modl
    
    166 166
                 let found = case mb_modbreaks of
    
    167 167
                       Nothing -> False
    
    168
    -                  Just mb -> fun_str `elem` (intercalate "." <$> elems (modBreaks_decls mb))
    
    168
    +                  Just mb -> fun_str `elem` (List.intercalate "." <$> elems (modBreaks_decls mb))
    
    169 169
                 if found
    
    170 170
                   then pure Nothing
    
    171 171
                   else pure $ Just $ text "No breakpoint found for" <+> quotes (text fun_str)
    
    ... ... @@ -182,7 +182,7 @@ findBreakForBind str_name modbreaks = filter (not . enclosed) ticks
    182 182
       where
    
    183 183
         ticks = [ (index, span)
    
    184 184
                 | (index, decls) <- assocs (modBreaks_decls modbreaks),
    
    185
    -              str_name == intercalate "." decls,
    
    185
    +              str_name == List.intercalate "." decls,
    
    186 186
                   RealSrcSpan span _ <- [modBreaks_locs modbreaks ! index] ]
    
    187 187
         enclosed (_,sp0) = any subspan ticks
    
    188 188
           where subspan (_,sp) = sp /= sp0 &&