[GHC] #14133: COMPLETE pragmas seem to be ignored when using view patterns

GHC ghc-devs at haskell.org
Thu Aug 17 11:47:52 UTC 2017


#14133: COMPLETE pragmas seem to be ignored when using view patterns
-------------------------------------+-------------------------------------
           Reporter:  jle            |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Incorrect
  Unknown/Multiple                   |  error/warning at compile-time
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE PatternSynonyms #-}

 pattern I :: Int -> Int
 pattern I x <- (id -> x)
 {-# COMPLETE I #-}

 foo :: Int -> Int
 foo (I x) = x + 3

 bar :: Int -> Int
 bar (id->I x) = x + 3

 main :: IO ()
 main = return ()
 }}}

 Raises a warning for `bar`:

 {{{
 Bug.hs:12:1: warning: [-Wincomplete-patterns]
     Pattern match(es) are non-exhaustive
     In an equation for 'bar': Patterns not matched: _
    |
 12 | bar (id->(I x)) = x + 3
    | ^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 but not for `foo`.

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


More information about the ghc-tickets mailing list