[GHC] #10997: Pattern synonym causes Iface error.

GHC ghc-devs at haskell.org
Thu Oct 22 19:34:29 UTC 2015


#10997: Pattern synonym causes Iface error.
-------------------------------------+-------------------------------------
        Reporter:  mpickering        |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.10.2
      Resolution:                    |             Keywords:
                                     |  PatternSynonyms
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
                                     |  typecheck/should_compile/T10997
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by Iceland_jack):

 I am also affected by this bug when using `-fobject-code`.

 Given

 {{{
 #!haskell
 {-# LANGUAGE GADTs, PatternSynonyms #-}

 module Foo where

 data Exp ty where
   LitB :: Bool -> Exp Bool

 pattern Tru :: b ~ Bool => Exp b
 pattern Tru = LitB True
 }}}

 and

 {{{
 #!haskell
 module Bar where

 import Foo

 foo :: Exp a -> String
 foo Tru = "True"
 }}}

 results in the following session:

 {{{
 % ghci -ignore-dot-ghci
 GHCi, version 7.10.2: http://www.haskell.org/ghc/  :? for help
 Prelude> :load Bar
 [1 of 2] Compiling Foo              ( Foo.hs, interpreted )
 [2 of 2] Compiling Bar              ( Bar.hs, interpreted )
 Ok, modules loaded: Bar, Foo.
 *Bar> :set -fobject-code
 *Bar> :load Foo
 [1 of 1] Compiling Foo              ( Foo.hs, Foo.o )
 Ok, modules loaded: Foo.
 Prelude Foo> :load Bar
 [2 of 2] Compiling Bar              ( Bar.hs, Bar.o )
 The interface for ‘Foo’
 Declaration for Tru
 Pattern synonym Tru:
   Iface type variable out of scope:  k
 Cannot continue after interface file error
 >
 }}}

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


More information about the ghc-tickets mailing list