[GHC] #11633: Record field order in a bidirectional pattern synonym match is order dependent

GHC ghc-devs at haskell.org
Wed Feb 24 10:56:51 UTC 2016


#11633: Record field order in a bidirectional pattern synonym match is order
dependent
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  high           |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
  PatternSynonyms                    |
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Consider this example,

 {{{#!hs
 {-# LANGUAGE PatternSynonyms #-}
 module Test where

 data ARecord = ARecord {anInt :: Int, aString :: String}

 -- This works...
 pattern AGoodPat :: Int -> String -> ARecord
 pattern AGoodPat n s = ARecord {anInt=n, aString=s}

 -- But if we invert the order of the fields things break...
 pattern ABadPat :: Int -> String -> ARecord
 pattern ABadPat n s = ARecord {aString=s, anInt=n}
 }}}

 Despite the fact that `AGoodPat` and `ABadPat` differ only in the order of
 the fields in their matches, `ABadPat` fails to typecheck with,

 {{{
 Test.hs:12:40: error:
     • Couldn't match type ‘[Char]’ with ‘Int’
       Expected type: Int
         Actual type: String
     • In the first argument of ‘ARecord’, namely ‘s’
       In the expression: ARecord s n
       In an equation for ‘$bABadPat’: $bABadPat n s = ARecord s n

 Test.hs:12:49: error:
     • Couldn't match type ‘Int’ with ‘[Char]’
       Expected type: String
         Actual type: Int
     • In the second argument of ‘ARecord’, namely ‘n’
       In the expression: ARecord s n
       In an equation for ‘$bABadPat’: $bABadPat n s = ARecord s n
 }}}

 This can be observed with both 7.10.3 and `master`.

 If one makes `ABadPat` into a one-directional pattern then the error
 vanishes. The fact that field order matters in the case of bi-directional
 record pattern synonyms seems a bit odd. If there's a good reason why this
 must be the case then fair enough, but we should make sure this is
 mentioned in the users guide and provide a more helpful error message.

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


More information about the ghc-tickets mailing list