[GHC] #10997: Pattern synonym causes Iface error.
GHC
ghc-devs at haskell.org
Wed Oct 21 12:03:05 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:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by mpickering):
Yes, see the attached file and run "stack build" in p2/ is one way.
Another way to trigger it is to have, two files `Foo.hs` and `Bar.hs` as
follows. Then run the following commands..
{{{
ghc Bar.hs
vim Bar.hs
.... make a simple change...
ghc Bar.hs
}}}
{{{
[2 of 2] Compiling Bar ( Bar.hs, Bar.o )
The interface for ‘Foo’
Declaration for Just'
Pattern synonym Just':
Iface type variable out of scope: k
Cannot continue after interface file error
}}}
{{{
{-# LANGUAGE PatternSynonyms, ViewPatterns, ConstraintKinds, TypeFamilies,
PolyKinds, KindSignatures #-}
module Foo where
import GHC.Exts
type family Showable (a :: k) :: Constraint where
Showable (a :: *) = (Show a)
Showable a = ()
extractJust :: Maybe a -> (Bool, a)
extractJust (Just a) = (True, a)
extractJust _ = (False, undefined)
pattern Just' :: () => (Showable a) => a -> (Maybe a)
pattern Just' a <- (extractJust -> (True, a)) where
Just' a = Just a
}}}
{{{
module Bar where
import Foo
bar :: (Showable a) => Maybe a -> Maybe a
bar (Just' a) = Just' a
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10997#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list