[GHC] #9584: Interface file errors (Iface type variable out of scope: k)

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: jonsterling | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- (Please forgive me if I have not formatted this bug report properly) Anyway, yesterday in a project at work we started having a strange problem where pretty much any change in our code at all would result in the next build failing with this error: {{{ The interface for ‘main:HList’ Declaration for $fRLensk:r_$s$w$crlens: Iface type variable out of scope: k Cannot continue after interface file error }}} I can get around the problem by deleting the dist directory, but this is very unfortunate, since it basically changes my build/test cycle from a few seconds to a minutes because I can't take advantage of the cached builds of things that *haven't* changed. It seems like errors like this have cropped up a few times in GHC, but they've always been fixed so far, so hopefully someone here will be familiar with what is causing this one! Please let me know if there is further information I can provide. The file in question looks basically like this: (it depends on some other stuff in our project, and so it won't build immediately if you paste it onto your machine; let me know if you need me to bundle it up into something self-contained). {{{#!hs -- | A bespoke record/HList type. 'el' interprets fields into types; 'tot' is -- the maximal extension of the record type; and 'rs' is the subset of 'tot' -- contained in the record itself. data Record (el :: k -> *) (tot :: [k]) (rs :: [k]) where Nil :: Record el tot '[] (:*) :: ( ElemTF r tot ?? '("the key", r, "is not permitted in this record, which may only contain", tot) , DistinctTF (r ': rs) ?? '("the key", r, "is already in", rs) ) => el r -> Record el tot rs -> Record el tot (r ': rs) infixr 9 :* -- | Records have lenses for their fields. class ElemTF r rs ~ True => RLens rs r where rlens :: proxy r -> CL.Lens' (Record el tot rs) (el r) instance RLens (r ': rs) r where rlens _ = CL.lens (\(x :* _) -> x) (\(_ :* xs) x -> x :* xs) instance (ElemTF r (s ': rs) ~ True, RLens rs r) => RLens (s ': rs) r where rlens _ = CL.lens (\(_ :* xs) -> xs ^. rlens Proxy) (\(x :* xs) y -> x :* xs & rlens Proxy .~ y) -- | Records with fields in 'K' give rise to a functor from 'Hask^K' to 'Hask'. (<<$>>) :: (forall x. f x -> g x) -> Record f tot rs -> Record g tot rs _ <<$>> Nil = Nil eta <<$>> (x :* xs) = eta x :* (eta <<$>> xs) infixl 8 <<$>> -- | Records can be traversed to pull out some of their effects. rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Record f tot rs -> h (Record g tot rs) rtraverse _ Nil = pure Nil rtraverse f (x :* xs) = (:*) <$> f x <*> rtraverse f xs -- | As a special case, we can yank out the first layer of effects in a -- composed functor stack. rtraverse1 :: Applicative f => Record (f :. g) tot rs -> f (Record g tot rs) rtraverse1 = rtraverse getCompose -- | Records whose fields are uniform in type may be turned into a list. recordToList :: Record (Const t) tbl rs -> [t] recordToList Nil = [] recordToList (Const x :* xs) = x : recordToList xs instance Show (Record el tot '[]) where show _ = "Nil" instance ( Show (Record el tot rs) , Show (el r) ) => Show (Record el tot (r ': rs)) where show (x :* xs) = "(" ++ show x ++ " :* " ++ show xs ++ ")" data family Sing (a :: k) class SingI a where sing :: Sing a class kparam ~ Any => SingE (kparam :: k) rep | kparam -> rep where fromSing :: Sing (a :: k) -> rep }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Looks bogus to me. Can you create a reproducible test case, as self- contained as possible? Thanks! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by thoughtpolice): FWIW, this looks quite similar to #9263. If you *can* boil this down at all to be a small self contained set of modules, that'd be great; I'd be willing to test if the fix for #9263 also fixes this (and if so, we can add this example as another test). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by jonsterling): Hi Simon! Not sure what you could mean by "bogus", but Austin Seipp's suggested me that this seems similar to #9253... I'll try and bundle this up into something testable as soon as possible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): By "bogus" I meant that GHC's behaviour looks very suspicious; a probable bug. But indeed a test case would enable us to find out. Thank you. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: #9263 None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * related: => #9263 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: | Owner: jonsterling | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: #9263 None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by AlexanderThiemann): I get this error when trying to run my test-suite: {{{ λ cabal test ./Spock.cabal has been changed. Re-configuring with most recently used options. If this fails, please run configure manually. Resolving dependencies... Configuring Spock-0.7.0.0... Building Spock-0.7.0.0... Preprocessing library Spock-0.7.0.0... [12 of 13] Compiling Web.Spock.Internal.TextRouting ( src/Web/Spock/Internal/TextRouting.hs, dist/build/Web/Spock/Internal/TextRouting.o ) [13 of 13] Compiling Web.Spock.Simple ( src/Web/Spock/Simple.hs, dist/build/Web/Spock/Simple.o ) In-place registering Spock-0.7.0.0... Preprocessing test suite 'spocktests' for Spock-0.7.0.0... [2 of 4] Compiling Web.Spock.SimpleSpec ( test/Web/Spock/SimpleSpec.hs, dist/build/spocktests/spocktests-tmp/Web/Spock/SimpleSpec.o ) /Users/athiemann/devel/Spock/dist/build/Web/Spock/Internal/TextRouting.hi Declaration for textRegistry1: Iface type variable out of scope: k Cannot continue after interface file error }}} I think I am stumbling over the issue on both GHC7.6 and GHC7.8. I'm not sure how I can create a smaller test case, so I'll just point you to the commit and the travis build: https://github.com/agrafix/Spock/tree/575fdb1332b719a23d84e1fbb67f097f22d64e... https://travis-ci.org/agrafix/Spock/builds/36477042 cabal clean "solves" the issue... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: jonsterling | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #9263 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by andreas.abel): I am getting a similar error (with ghc 7.8.3) when compiling Agda for the second time (without removing dist). Probably cause is SPECIALIZE pragmas. https://github.com/agda/agda/commit/22eb932c0df278e40e40c6e990d2e9dcb6f99449 Probably reproducible by * cloning Agda at this commit * introduce an error in a later module, e.g. src/full/Agda/TypeChecking/InstanceArguments.hs * make install-bin * fix the error * make install-bin Error: {{{ The interface for ‘Agda-2.4.3:Agda.TypeChecking.Free.Lazy’ Rule SPEC $cfreeVars': Iface type variable out of scope: a Cannot continue after interface file error cabal: Error: some packages failed to install: }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: jonsterling | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #9263 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Do you get the error with 7.10? We are unlikely to release another version of 7.8, unless it's mission critical to a significant chunk of users. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: jonsterling | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #9263 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by andreas.abel): This issue nudged me to install ghc 7.10. With 7.10, this problem does not occur. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9584: Interface file errors (Iface type variable out of scope: k) -------------------------------------+------------------------------------- Reporter: jonsterling | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #9263 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => wontfix Comment: OK good! I'll close as won't-fix. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9584#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC