Case split uncovered patterns in warnings or not?
Vladislav Zavialov
vladislav at serokell.io
Wed Nov 10 09:51:03 UTC 2021
Integer is an interesting example. I think it reveals another issue: exhaustiveness checking should account for abstract data types. If the constructors are not exported, do not case split.
- Vlad
> On 10 Nov 2021, at 12:48, Oleg Grenrus <oleg.grenrus at iki.fi> wrote:
>
> It should not. Not even when forced.
>
> I have seen an `Integer` constructors presented to me, for example:
>
> module Ex where
>
> foo :: Bool -> Integer -> Integer
> foo True i = i
>
> With GHC-8.8 the warning is good:
>
> % ghci-8.8.4 -Wall Ex.hs
> GHCi, version 8.8.4: https://www.haskell.org/ghc/ :? for help
> Loaded GHCi configuration from /home/phadej/.ghci
> [1 of 1] Compiling Ex ( Ex.hs, interpreted )
>
> Ex.hs:4:1: warning: [-Wincomplete-patterns]
> Pattern match(es) are non-exhaustive
> In an equation for ‘foo’: Patterns not matched: False _
> |
> 4 | foo True i = i
> | ^^^^^^^^^^^^^^
>
> With GHC-8.10 is straight up awful.
> I'm glad I don't have to explain it to any beginner,
> or person who don't know how Integer is implemented.
> (9.2 is about as bad too).
>
> % ghci-8.10.4 -Wall Ex.hs
> GHCi, version 8.10.4: https://www.haskell.org/ghc/ :? for help
> Loaded GHCi configuration from /home/phadej/.ghci
> [1 of 1] Compiling Ex ( Ex.hs, interpreted )
>
> Ex.hs:4:1: warning: [-Wincomplete-patterns]
> Pattern match(es) are non-exhaustive
> In an equation for ‘foo’:
> Patterns not matched:
> False (integer-gmp-1.0.3.0:GHC.Integer.Type.S# _)
> False (integer-gmp-1.0.3.0:GHC.Integer.Type.Jp# _)
> False (integer-gmp-1.0.3.0:GHC.Integer.Type.Jn# _)
> |
> 4 | foo True i = i
> | ^^^
>
> - Oleg
>
>
> On 9.11.2021 15.17, Sebastian Graf wrote:
>> Hi Devs,
>>
>> In https://gitlab.haskell.org/ghc/ghc/-/issues/20642 we saw that GHC >= 8.10 outputs pattern match warnings a little differently than it used to. Example from there:
>>
>> {-# OPTIONS_GHC -Wincomplete-uni-patterns #-}
>>
>> foo :: [a] -> [a]
>> foo [] = []
>> foo xs = ys
>> where
>> (_, ys@(_:_)) = splitAt 0 xs
>>
>> main :: IO ()
>> main = putStrLn $ foo $ "Hello, coverage checker!"
>> Instead of saying
>>
>>
>>
>> ListPair.hs:7:3: warning: [-Wincomplete-uni-patterns]
>> Pattern match(es) are non-exhaustive
>> In a pattern binding: Patterns not matched: (_, [])
>>
>>
>>
>> We now say
>>
>>
>>
>> ListPair.hs:7:3: warning: [-Wincomplete-uni-patterns]
>> Pattern match(es) are non-exhaustive
>> In a pattern binding:
>> Patterns of type ‘([a], [a])’ not matched:
>> ([], [])
>> ((_:_), [])
>>
>>
>>
>> E.g., newer versions do (one) case split on pattern variables that haven't even been scrutinised by the pattern match. That amounts to quantitatively more pattern suggestions and for each variable a list of constructors that could be matched on.
>> The motivation for the change is outlined in https://gitlab.haskell.org/ghc/ghc/-/issues/20642#note_390110, but I could easily be swayed not to do the case split. Which arguably is less surprising, as Andreas Abel points out.
>>
>> Considering the other examples from my post, which would you prefer?
>>
>> Cheers,
>> Sebastian
>>
>>
>> _______________________________________________
>> ghc-devs mailing list
>>
>> ghc-devs at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
More information about the ghc-devs
mailing list