[GHC] #15012: "Iface type variable out of scope" when compiling with -c
GHC
ghc-devs at haskell.org
Sun Apr 8 00:42:43 UTC 2018
#15012: "Iface type variable out of scope" when compiling with -c
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Take these two files:
{{{#!hs
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
module Foo where
import GHC.Generics
type FakeOut a = Int
data family TyFamily y z
data instance TyFamily a b = TyFamily Int (FakeOut b)
deriving Generic1
}}}
{{{#!hs
module Bar where
import Foo
import GHC.Generics
main :: IO ()
main = print $ from1 $ TyFamily 1 2
}}}
And compile them like so:
{{{
$ ghc -c Foo.hs
$ ghc -c Bar.hs
./Foo.hi
Declaration for Rep1_R:TyFamilyab
Axiom branches Rep1_R:TyFamilyab:
Iface type variable out of scope: b
Cannot continue after interface file error
}}}
I can reproduce this with every version of GHC from 7.8.4 onward, so this
is quite an old bug!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15012>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list