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

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following partial function will pass {{{-Wall}}} {{{#!haskell -- program 1 {-# LANGUAGE MultiWayIf #-} foo :: Bool -> Int foo b = if | b -> 23 }}} While the following two alternatives will not: {{{#!haskell -- program 2 foo :: Bool -> Int foo b | b = 23 }}} {{{#!haskell -- program 3 foo :: Bool -> Int foo b = case () of () | b -> 23 }}} Note that the GHC User's Guide states that "program 1" and "program 3" are equivalent. 1. Is this a bug or by design? 2. I guess at the very least we would want to update the User's Guide -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think it's a bug, or at least an inconsistency. Would someone like to fix it? I doubt it's difficult. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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 RyanGlScott): * keywords: => PatternMatchWarnings -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sigh. I don't see an easy way to fix this. The issue is that the entry- point into the pattern match coverage checker, `checkMatches`, requires a list of `LPat`s as its arguments. However, the AST for multi-way-`if` (`HsMultiIf`) has `GRHS`es, not `LPat`s. That's the same reason why this program doesn't emit any warnings under `-Wall`: {{{#!hs b :: Bool Just b | False = Nothing }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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: | -------------------------------------+------------------------------------- Comment (by simonpj): The pattern-match overlap checker can do some simple things with guards, if memory serves; but it would indeed need a new entry point. At the moment we lack anyone with the time and inclination to pay attention to the pattern-match overlap checker. There's a great paper about it, but the actual implementation needs love and care. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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: | -------------------------------------+------------------------------------- Comment (by jmct): Is this the "GADTs Meet Their Match" (great title) paper? I can try to take this on if no one else has cycles for it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, that's the paper! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): On second thought, I was too hasty in my earlier assessment—this might be more tractable than I thought. It turns out that when we're checking patterns from function bindings (as in `program 2` above), we don't directly call `checkMatches`, but instead go through an auxiliary function called [http://git.haskell.org/ghc.git/blob/6edafe3be0133fe69581fb3851a812c69ab9dbf7... matchWrapper]. Instead of taking a list of `LPat`s an an argument, `matchWrapper` takes a `MatchGroup`, and sets up the necessary scaffolding to feed that into `checkMatches`. Now, we can't directly feel an `HsMultiIf`'s guards into `matchWrapper`, since `HsMultiIf` has an `LGRHS` instead of a `MatchGroup`. However, if we look at the definition of `MatchGroup` (and `(L)Match`): {{{#!hs data MatchGroup p body = MG { mg_alts :: Located [LMatch p body] , mg_arg_tys :: [PostTc p Type] , mg_res_ty :: PostTc p Type , mg_origin :: Origin } type LMatch id body = Located (Match id body) data Match p body = Match { m_ctxt :: HsMatchContext (NameOrRdrName (IdP p)), m_pats :: [LPat p], -- The patterns m_grhss :: (GRHSs p body) } }}} We can see that we're actually very close to having what we need, since we can slide the `GRHS` right into a `Match`, and put that into the `mg_alts` of a `MatchGroup`. The trick is to then come up with suitable things to put in the remaining fields of `MatchGroup` and `Match`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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: | -------------------------------------+------------------------------------- Comment (by sighingnow): I'm confused with the following comments at Check.hs: https://ghc.haskell.org/trac/ghc/browser/ghc/compiler/deSugar/Check.hs#L1904 {{{#!hs 1904 exhaustiveWarningFlag (StmtCtxt {}) = Nothing -- Don't warn about incomplete patterns 1905 -- in list comprehensions, pattern guards 1906 -- etc. They are often *supposed* to be 1907 -- incomplete }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: patch 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: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * status: new => patch * testcase: => T14773a,T14773b * differential: => Phab:D4400 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: patch 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: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Why do you need `vanillaLPat`? Why not just have an empty list of patterns? Also {{{ b :: Bool Just b | False = Nothing }}} No that is not ignored by design. The thing that is ignored is this: {{{ [ e | False <- blah, blah blah ] and do { False <- blah; ... } }}} I hope that `StmtCxt` is true of the latter two but not of the former. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Why do you need `vanillaLPat`? Why not just have an empty list of
#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: patch 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: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sighingnow): Replying to [comment:11 simonpj]: patterns? I have misunderstood the `m_pats` field of `Match` and the `vars` arguments of `checkMatches`. I'll fix it.
I hope that `StmtCxt` is true of the latter two but not of the former.
Now I see that we can't use `StmtCtx` here. Could I add another context for the `False` guards in ?
{{{ b :: Bool Just b | False = Nothing }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14773: MultiWayIf makes it easy to write partial programs that are not catched by
-Wall
-------------------------------------+-------------------------------------
Reporter: SimonHengel | Owner: sighingnow
Type: bug | Status: patch
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:
| T14773a,T14773b
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4400
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14773#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC