Exhaustiveness checking for pattern synonyms

Simon Peyton Jones simonpj at microsoft.com
Tue Jan 10 16:05:34 UTC 2017


Questions

* What if there are multiple COMPLETE pragmas e.g.
  {-# COMPLETE A, B, C #-}
  {-# COMPLETE A, X, Y, Z #-}
  Is that ok?  I guess it should be!

  Will the pattern-match exhaustiveness check then succeed
  if a function uses either set?

  What happens if you use a mixture of constructors in a match
  (e.g. A, X, C, Z)?  Presumably all bets are off?

* Note that COMPLETE pragmas could be a new source of orphan modules
     module M where
       import N( pattern P, pattern Q )
       {-# COMPLETE P, Q #-}
  where neither P nor Q is defined in M.  Then every module that is
  transitively "above" M would need to read M.hi just in case its
  COMPLETE pragmas was relevant.

* Point out in the spec that COMPLETE pragmas are entirely unchecked.
  It's up to the programmer to get it right.

* Typing.  What does it mean for the types to "agree" with each other.
  E.g  A :: a -> [(a, Int)]
       B :: b -> [(Int, b)]
  Is this ok?  Please say explicitly with examples.

* I didn't really didn't understand the "Error messages" section.


Simon

|  -----Original Message-----
|  From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Matthew
|  Pickering
|  Sent: 22 November 2016 10:43
|  To: GHC developers <ghc-devs at haskell.org>
|  Subject: Exhaustiveness checking for pattern synonyms
|  
|  Hello devs,
|  
|  I have implemented exhaustiveness checking for pattern synonyms. The idea is
|  very simple, you specify a set of pattern synonyms (or data
|  constructors) which are regarded as a complete match.
|  The pattern match checker then uses this information in order to check
|  whether a function covers all possibilities.
|  
|  Specification:
|  
|  https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/CompleteSigs
|  
|  https://phabricator.haskell.org/D2669
|  https://phabricator.haskell.org/D2725
|  
|  https://ghc.haskell.org/trac/ghc/ticket/8779
|  
|  Matt
|  _______________________________________________
|  ghc-devs mailing list
|  ghc-devs at haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell
|  .org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devs&data=02%7C01%7Csimonpj%40microsoft.com%7C155eb2786cb040d8052908d412c453
|  b5%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636154081815249356&sdata=MkQ
|  FpwJWaTU%2BdEQSYEBjXLt80BrXLkBp9V8twdKB6BI%3D&reserved=0


More information about the ghc-devs mailing list