[GHC] #14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall

GHC ghc-devs at haskell.org
Fri Feb 9 02:11:59 UTC 2018


#14773: MultiWayIf makes it easy to write partial programs that are not catched by
-Wall
-------------------------------------+-------------------------------------
        Reporter:  SimonHengel       |                Owner:  sighingnow
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:
                                     |  PatternMatchWarnings
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by sighingnow):

 * owner:  (none) => sighingnow


Comment:

 I already have some tries on this. We can construct the `LMatch` manually
 in `ds_expr`, the use `checkMatches` directly, without feed to
 `matchWrapper`. We can do some like this:

 {{{#!hs
 ds_expr _ (HsMultiIf res_ty alts)
   | null alts
   = mkErrorExpr

   | otherwise
   = do { match_result <- liftM (foldr1 combineMatchResults)
                                (mapM (dsGRHS IfAlt res_ty) alts)
        ; dflags <- getDynFlags
        ; vanillaId <- mkPmId boolTy
        ; let vanillaLPat = mkLHsVarPatTup [vanillaId]
              matches = [ L (getLoc pattern) $
                             Match { m_ctxt = IfAlt
                                   , m_pats = [vanillaLPat]
                                   , m_grhss = GRHSs [pattern] (noLoc
 emptyLocalBinds) }
                                   -- mkSimpleMatch IfAlt [vanillaLPat] m
                        | pattern@(L _ (GRHS p m)) <- alts]
        ; checkMatches dflags dsMatchContext [vanillaId] matches

        ; error_expr   <- mkErrorExpr
        ; extractMatchResult match_result error_expr }
   where
     mkErrorExpr = mkErrorAppDs nON_EXHAUSTIVE_GUARDS_ERROR_ID res_ty
                                (text "multi-way if")

     combinedLoc = foldr1 combineSrcSpans (map getLoc alts)
     dsMatchContext = DsMatchContext IfAlt combinedLoc
 }}}

 Patch coming!

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14773#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list