Can't find interface-file declaration for type constructor or class integer-gmp:GHC.Integer.Type.Integer

Johan Tibell johan.tibell at gmail.com
Thu Aug 18 18:58:01 CEST 2011


I shouldn't have to modify PrelNames since I kept GHC.Integer.Type,
no? Or does PrelNames have to contain the name of the module that
originally defined the type? Looking in the .hi file in question (the
one for GHC.Integer.Type) I can see both the export of Integer(..) and
the import of Integer(..) from GHC.Integer.GMP.Types.

On Thu, Aug 18, 2011 at 6:10 PM, Simon Peyton-Jones
<simonpj at microsoft.com> wrote:
> My guess is that you have not updated compiler/prelude/PrelNames, which contains wired-in knowledge of which modules certain functions and data types live in.  Check the ones you've moved!
>
> S
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
> | bounces at haskell.org] On Behalf Of Johan Tibell
> | Sent: 18 August 2011 15:45
> | To: glasgow-haskell-users
> | Subject: Can't find interface-file declaration for type constructor or class integer-
> | gmp:GHC.Integer.Type.Integer
> |
> | I'm trying to refactor the integer-gmp package to fix the breakage
> | explained in #5384. During the refactoring I
> |
> | * moved GHC.Integer.Type to GHC.Integer.GMP.Type, and
> | * added a new GHC.Integer.Type module that re-exports parts of the
> | interface now exposed by GHC.Integer.GMP.Type
> |
> | The content of GHC.Integer.Type is just:
> |
> | {-# LANGUAGE NoImplicitPrelude #-}
> | {-# OPTIONS_HADDOCK hide #-}
> |
> | -- If you change the module name or the export list you must update
> | -- compiler/prelude/PrelNames.lhs.
> | module GHC.Integer.Type (
> |       Integer(..)
> |     , plusInteger
> |     , timesInteger
> |     , smallInteger
> |     , integerToWord
> |     , integerToInt
> |     , minusInteger
> |     , negateInteger
> |     , eqInteger
> |     , neqInteger
> |     , absInteger
> |     , signumInteger
> |     , leInteger
> |     , gtInteger
> |     , ltInteger
> |     , geInteger
> |     , compareInteger
> |     , gcdInteger
> |     , lcmInteger
> |     , andInteger
> |     , orInteger
> |     , xorInteger
> |     , complementInteger
> |     , shiftLInteger
> |     , shiftRInteger
> |     ) where
> |
> | import GHC.Integer.GMP.Type
> |
> | GHC doesn't seem to like this at all. It can no longer find the
> | GHC.Integer.Type.Integer type:
> |
> | $ "inplace/bin/ghc-stage1"   -H64m -O -fasm    -package-name
> | base-4.4.0.0 -hide-all-packages -i -ilibraries/base/.
> | -ilibraries/base/dist-install/build
> | -ilibraries/base/dist-install/build/autogen
> | -Ilibraries/base/dist-install/build
> | -Ilibraries/base/dist-install/build/autogen -Ilibraries/base/include
> | -optP-DOPTIMISE_INTEGER_GCD_LCM -optP-include
> | -optPlibraries/base/dist-install/build/autogen/cabal_macros.h -package
> | ghc-prim-0.2.0.0 -package integer-gmp-0.3.0.0 -package rts-1.0
> | -package-name base -XHaskell98 -XCPP -O -dcore-lint
> | -no-user-package-conf -rtsopts     -odir
> | libraries/base/dist-install/build -hidir
> | libraries/base/dist-install/build -stubdir
> | libraries/base/dist-install/build -hisuf hi -osuf  o -hcsuf hc -c
> | libraries/base/./Data/Maybe.hs -o
> | libraries/base/dist-install/build/Data/Maybe.o
> |
> | libraries/base/Data/Maybe.hs:70:13:
> |     Can't find interface-file declaration for type constructor or
> | class integer-gmp:GHC.Integer.Type.Integer
> |       Probable cause: bug in .hi-boot file, or inconsistent .hi file
> |       Use -ddump-if-trace to get an idea of which file caused the error
> |     When deriving the instance for (Eq (Maybe a))
> |
> | Here's the -ddump-if-trace log:
> |
> | $ "inplace/bin/ghc-stage1"   -H64m -O -fasm    -package-name
> | base-4.4.0.0 -hide-all-packages -i -ilibraries/base/.
> | -ilibraries/base/dist-install/build
> | -ilibraries/base/dist-install/build/autogen
> | -Ilibraries/base/dist-install/build
> | -Ilibraries/base/dist-install/build/autogen -Ilibraries/base/include
> | -optP-DOPTIMISE_INTEGER_GCD_LCM -optP-include
> | -optPlibraries/base/dist-install/build/autogen/cabal_macros.h -package
> | ghc-prim-0.2.0.0 -package integer-gmp-0.3.0.0 -package rts-1.0
> | -package-name base -XHaskell98 -XCPP -O -dcore-lint
> | -no-user-package-conf -rtsopts     -odir
> | libraries/base/dist-install/build -hidir
> | libraries/base/dist-install/build -stubdir
> | libraries/base/dist-install/build -hisuf hi -osuf  o -hcsuf hc -c
> | libraries/base/./Data/Maybe.hs -o
> | libraries/base/dist-install/build/Data/Maybe.o -ddump-if-trace
> | FYI: cannont read old interface file:
> |     libraries/base/dist-install/build/Data/Maybe.hi: openBinaryFile:
> | does not exist (No such file or directory)
> | Considering whether to load base:GHC.Base
> | Reading interface for base:GHC.Base;
> |     reason: GHC.Base is directly imported
> | readIFace libraries/base/dist-install/build/GHC/Base.hi
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Generics
> | Reading interface for ghc-prim:GHC.Generics;
> |     reason: GHC.Generics is directly imported
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
> | install/build/GHC/Generics.hi
> | updating EPS_
> | updating EPS_
> | Considering whether to load base:GHC.Base {- SYSTEM -}
> | loadHiBootInterface base:Data.Maybe
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | Reading interface for ghc-prim:GHC.Types;
> |     reason: Checking fixity for :
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
> | install/build/GHC/Types.hi
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | Starting fork { Declaration for Monad
> | Loading decl for GHC.Base.Monad
> | updating EPS_
> | buildClass
> | buildClass GHC.Base.T:Monad
> | } ending fork Declaration for Monad
> | Starting fork { Declaration for Functor
> | Loading decl for GHC.Base.Functor
> | updating EPS_
> | buildClass
> | buildClass GHC.Base.T:Functor
> | } ending fork Declaration for Functor
> | tcImportDecl GHC.Classes.Eq
> | Need decl for GHC.Classes.Eq
> | Considering whether to load ghc-prim:GHC.Classes {- SYSTEM -}
> | Reading interface for ghc-prim:GHC.Classes;
> |     reason: Need decl for GHC.Classes.Eq
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
> | install/build/GHC/Classes.hi
> | updating EPS_
> | Starting fork { Declaration for Eq
> | Loading decl for GHC.Classes.Eq
> | updating EPS_
> | buildClass
> | buildClass GHC.Classes.T:Eq
> | } ending fork Declaration for Eq
> | Starting fork { Declaration for Ord
> | Loading decl for GHC.Classes.Ord
> | updating EPS_
> | buildClass
> | buildClass GHC.Classes.T:Ord
> | } ending fork Declaration for Ord
> | Starting fork { Declaration for Generic
> | Loading decl for GHC.Generics.Generic
> | updating EPS_
> | buildClass
> | buildClass GHC.Generics.T:Generic
> | } ending fork Declaration for Generic
> | Starting fork { Declaration for D1
> | Loading decl for GHC.Generics.D1
> | updating EPS_
> | } ending fork Declaration for D1
> | Starting fork { Declaration for C1
> | Loading decl for GHC.Generics.C1
> | updating EPS_
> | } ending fork Declaration for C1
> | Starting fork { Declaration for S1
> | Loading decl for GHC.Generics.S1
> | updating EPS_
> | } ending fork Declaration for S1
> | Starting fork { Declaration for NoSelector
> | Loading decl for GHC.Generics.NoSelector
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.NoSelector
> | } ending fork Declaration for NoSelector
> | Starting fork { Declaration for Rec0
> | Loading decl for GHC.Generics.Rec0
> | updating EPS_
> | } ending fork Declaration for Rec0
> | Starting fork { Declaration for Par0
> | Loading decl for GHC.Generics.Par0
> | updating EPS_
> | } ending fork Declaration for Par0
> | Starting fork { Declaration for U1
> | Loading decl for GHC.Generics.U1
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.U1
> | } ending fork Declaration for U1
> | Starting fork { Declaration for V1
> | Loading decl for GHC.Generics.V1
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.V1
> | } ending fork Declaration for V1
> | Starting fork { Declaration for :+:
> | Loading decl for GHC.Generics.:+:
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.:+:
> | } ending fork Declaration for :+:
> | Starting fork { Declaration for :*:
> | Loading decl for GHC.Generics.:*:
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.:*:
> | } ending fork Declaration for :*:
> | Starting fork { Declaration for Datatype
> | Loading decl for GHC.Generics.Datatype
> | updating EPS_
> | buildClass
> | buildClass GHC.Generics.T:Datatype
> | } ending fork Declaration for Datatype
> | Starting fork { Declaration for Constructor
> | Loading decl for GHC.Generics.Constructor
> | updating EPS_
> | buildClass
> | buildClass GHC.Generics.T:Constructor
> | } ending fork Declaration for Constructor
> | Starting fork { Declaration for Selector
> | Loading decl for GHC.Generics.Selector
> | updating EPS_
> | buildClass
> | mkNewTyConRhs GHC.Generics.NTCo:T:Selector
> | buildClass GHC.Generics.T:Selector
> | } ending fork Declaration for Selector
> | Starting fork { Dict fun GHC.Classes.$fEq[]
> | Starting fork { Declaration for $fEq[]
> | Loading decl for GHC.Classes.$fEq[]
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEq[]
> | } ending fork Dict fun GHC.Classes.$fEq[]
> | Starting fork { Dict fun GHC.Classes.$fEqOrdering
> | Starting fork { Declaration for $fEqOrdering
> | Loading decl for GHC.Classes.$fEqOrdering
> | updating EPS_
> | Need decl for GHC.Ordering.Ordering
> | Considering whether to load ghc-prim:GHC.Ordering {- SYSTEM -}
> | Reading interface for ghc-prim:GHC.Ordering;
> |     reason: Need decl for GHC.Ordering.Ordering
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
> | install/build/GHC/Ordering.hi
> | updating EPS_
> | } ending fork Declaration for $fEqOrdering
> | } ending fork Dict fun GHC.Classes.$fEqOrdering
> | Starting fork { Declaration for Ordering
> | Loading decl for GHC.Ordering.Ordering
> | updating EPS_
> | tcIfaceDecl4 GHC.Ordering.Ordering
> | } ending fork Declaration for Ordering
> | Starting fork { Dict fun GHC.Classes.$fEqInt
> | Starting fork { Declaration for $fEqInt
> | Loading decl for GHC.Classes.$fEqInt
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEqInt
> | } ending fork Dict fun GHC.Classes.$fEqInt
> | Starting fork { Dict fun GHC.Classes.$fEqFloat
> | Starting fork { Declaration for $fEqFloat
> | Loading decl for GHC.Classes.$fEqFloat
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEqFloat
> | } ending fork Dict fun GHC.Classes.$fEqFloat
> | Starting fork { Dict fun GHC.Classes.$fEqFixity
> | Starting fork { Declaration for $fEqFixity
> | Loading decl for GHC.Classes.$fEqFixity
> | updating EPS_
> | } ending fork Declaration for $fEqFixity
> | } ending fork Dict fun GHC.Classes.$fEqFixity
> | Starting fork { Declaration for Fixity
> | Loading decl for GHC.Generics.Fixity
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.Fixity
> | } ending fork Declaration for Fixity
> | Starting fork { Dict fun GHC.Classes.$fEqDouble
> | Starting fork { Declaration for $fEqDouble
> | Loading decl for GHC.Classes.$fEqDouble
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEqDouble
> | } ending fork Dict fun GHC.Classes.$fEqDouble
> | Starting fork { Dict fun GHC.Classes.$fEqChar
> | Starting fork { Declaration for $fEqChar
> | Loading decl for GHC.Classes.$fEqChar
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEqChar
> | } ending fork Dict fun GHC.Classes.$fEqChar
> | Starting fork { Dict fun GHC.Classes.$fEqBool
> | Starting fork { Declaration for $fEqBool
> | Loading decl for GHC.Classes.$fEqBool
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
> | } ending fork Declaration for $fEqBool
> | } ending fork Dict fun GHC.Classes.$fEqBool
> | Starting fork { Dict fun GHC.Classes.$fEqAssociativity
> | Starting fork { Declaration for $fEqAssociativity
> | Loading decl for GHC.Classes.$fEqAssociativity
> | updating EPS_
> | } ending fork Declaration for $fEqAssociativity
> | } ending fork Dict fun GHC.Classes.$fEqAssociativity
> | Starting fork { Declaration for Associativity
> | Loading decl for GHC.Generics.Associativity
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.Associativity
> | } ending fork Declaration for Associativity
> | Starting fork { Dict fun GHC.Classes.$fEqArity
> | Starting fork { Declaration for $fEqArity
> | Loading decl for GHC.Classes.$fEqArity
> | updating EPS_
> | } ending fork Declaration for $fEqArity
> | } ending fork Dict fun GHC.Classes.$fEqArity
> | Starting fork { Declaration for Arity
> | Loading decl for GHC.Generics.Arity
> | updating EPS_
> | tcIfaceDecl4 GHC.Generics.Arity
> | } ending fork Declaration for Arity
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | Reading interface for ghc-prim:GHC.Tuple;
> |     reason: Need home interface for wired-in thing (,,,,,,,,,,,,,,)
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
> | install/build/GHC/Tuple.hi
> | updating EPS_
> | } ending fork Declaration for $fEq(,,,,,,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,,)
> | Starting fork { Declaration for $fEq(,,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,,)
> | Starting fork { Declaration for $fEq(,,,,)
> | Loading decl for GHC.Classes.$fEq(,,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,,)
> | Starting fork { Declaration for $fEq(,,,)
> | Loading decl for GHC.Classes.$fEq(,,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,,)
> | Starting fork { Declaration for $fEq(,,)
> | Loading decl for GHC.Classes.$fEq(,,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,,)
> | } ending fork Dict fun GHC.Classes.$fEq(,,)
> | Starting fork { Dict fun GHC.Classes.$fEq(,)
> | Starting fork { Declaration for $fEq(,)
> | Loading decl for GHC.Classes.$fEq(,)
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Tuple {- SYSTEM -}
> | } ending fork Declaration for $fEq(,)
> | } ending fork Dict fun GHC.Classes.$fEq(,)
> | Starting fork { Dict fun GHC.Classes.$fEq()
> | Starting fork { Declaration for $fEq()
> | Loading decl for GHC.Classes.$fEq()
> | updating EPS_
> | Considering whether to load ghc-prim:GHC.Unit {- SYSTEM -}
> | Reading interface for ghc-prim:GHC.Unit;
> |     reason: Need home interface for wired-in thing ()
> | readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-install/build/GHC/Unit.hi
> | updating EPS_
> | } ending fork Declaration for $fEq()
> | } ending fork Dict fun GHC.Classes.$fEq()
> | tcImportDecl GHC.Integer.Type.Integer
> | Need decl for GHC.Integer.Type.Integer
> | Considering whether to load integer-gmp:GHC.Integer.Type {- SYSTEM -}
> | Reading interface for integer-gmp:GHC.Integer.Type;
> |     reason: Need decl for GHC.Integer.Type.Integer
> | readIFace /usr/local/google/src/ghc/libraries/integer-gmp/dist-
> | install/build/GHC/Integer/Type.hi
> | updating EPS_
> |
> | libraries/base/Data/Maybe.hs:70:13:
> |     Can't find interface-file declaration for type constructor or
> | class integer-gmp:GHC.Integer.Type.Integer
> |       Probable cause: bug in .hi-boot file, or inconsistent .hi file
> |       Use -ddump-if-trace to get an idea of which file caused the error
> |     When deriving the instance for (Eq (Maybe a))
> |
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>



More information about the Glasgow-haskell-users mailing list