Skip to content
GitLab
Projects Groups Snippets
  • /
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 5,348
    • Issues 5,348
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 573
    • Merge requests 573
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell CompilerGlasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #9584
Closed
Open
Issue created Sep 12, 2014 by jonsterling@trac-jonsterling

Interface file errors (Iface type variable out of scope: k)

(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).

-- | 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
Trac metadata
Trac field Value
Version 7.8.3
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Assignee
Assign to
Time tracking