Bodigrim pushed to branch wip/warning-for-last-and-init at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
    1 1
     {-# LANGUAGE Trustworthy #-}
    
    2 2
     {-# LANGUAGE LambdaCase #-}
    
    3
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    3 4
     -- | contains a prettyprinter for the
    
    4 5
     -- Template Haskell datatypes
    
    5 6
     
    
    ... ... @@ -13,7 +14,7 @@ import GHC.Boot.TH.PprLib
    13 14
     import GHC.Boot.TH.Syntax
    
    14 15
     import Data.Word ( Word8 )
    
    15 16
     import Data.Char ( toLower, chr )
    
    16
    -import Data.List ( intersperse, unsnoc )
    
    17
    +import Data.List ( intersperse )
    
    17 18
     import GHC.Show  ( showMultiLineString )
    
    18 19
     import GHC.Lexeme( isVarSymChar )
    
    19 20
     import Data.Ratio ( numerator, denominator )
    
    ... ... @@ -214,10 +215,9 @@ pprExp i (MDoE m ss_) = parensIf (i > noPrec) $
    214 215
         pprStms [s] = ppr s
    
    215 216
         pprStms ss  = braces (semiSep ss)
    
    216 217
     
    
    218
    +pprExp _ (CompE []) = text "<<Empty CompExp>>"
    
    217 219
     -- This will probably break with fixity declarations - would need a ';'
    
    218
    -pprExp _ (CompE ss) = case unsnoc ss of
    
    219
    -  Nothing -> text "<<Empty CompExp>>"
    
    220
    -  Just (ss', s) ->
    
    220
    +pprExp _ (CompE ss) =
    
    221 221
         if null ss'
    
    222 222
            -- If there are no statements in a list comprehension besides the last
    
    223 223
            -- one, we simply treat it like a normal list.
    
    ... ... @@ -226,6 +226,8 @@ pprExp _ (CompE ss) = case unsnoc ss of
    226 226
             <+> bar
    
    227 227
             <+> commaSep ss'
    
    228 228
              <> text "]"
    
    229
    +  where s = last ss
    
    230
    +        ss' = init ss
    
    229 231
     pprExp _ (ArithSeqE d) = ppr d
    
    230 232
     pprExp _ (ListE es) = brackets (commaSep es)
    
    231 233
     pprExp i (SigE e t) = parensIf (i > noPrec) $ pprExp sigPrec e