ghci confused by hi files

Yitzchak Gale gale at sefer.org
Tue Jan 16 06:12:26 EST 2007


I have observed the following weird behavior:

When I define an instance of a certain MPTC
in a separate module from the definition of
the class, ghci's ability to recognize the
methods of the class seems to vary depending
on whether or not hi files exist for the modules.

I am using the current Debian build of GHC 6.6.

Below are a set of three files that reproduce the
behavior, and a shell session that demonstrates
it.

Before I compile the program, ghci works fine.
After I compile with ghc  - thus generating hi files -
ghci gets confused. Then I delete the hi files
and everything is fine again.

Thanks,
Yitz

-- File Oops.hs

{-# OPTIONS_GHC -fglasgow-exts #-}
module Oops where
class Oops a b c | a -> b c where
  foo :: a -> b -> a

-- File Whoops.hs

{-# OPTIONS_GHC -fglasgow-exts #-}
module Whoops where
import Oops
instance Oops String Int Bool where
  foo x n = show (x, n)

-- File runWhoops.hs

module Main where
import Whoops
import Oops
main = putStrLn $ foo "bar" 42

$ ghci Whoops
 / /_\// /_/ / /  | |      GHC Interactive, version 6.6, for Haskell 98.
Loading package base ... linking ... done.
[1 of 2] Compiling Oops             ( Oops.hs, interpreted )
[2 of 2] Compiling Whoops           ( Whoops.hs, interpreted )
Ok, modules loaded: Oops, Whoops.
*Whoops> foo "baz" 7
"(\"baz\",7)"
*Whoops> Leaving GHCi.
$ ghc --make runWhoops.hs
[1 of 3] Compiling Oops             ( Oops.hs, Oops.o )
[2 of 3] Compiling Whoops           ( Whoops.hs, Whoops.o )
[3 of 3] Compiling Main             ( runWhoops.hs, runWhoops.o )
Linking runWhoops ...
$ ghci Whoops
 / /_\// /_/ / /  | |      GHC Interactive, version 6.6, for Haskell 98.
Loading package base ... linking ... done.
Ok, modules loaded: Oops, Whoops.
Prelude Whoops> foo "baz" 7

<interactive>:1:0: Not in scope: `foo'
Prelude Whoops> Leaving GHCi.
$ rm *.hi
$ ghci Whoops
 / /_\// /_/ / /  | |      GHC Interactive, version 6.6, for Haskell 98.
Loading package base ... linking ... done.
[1 of 2] Compiling Oops             ( Oops.hs, interpreted )
[2 of 2] Compiling Whoops           ( Whoops.hs, interpreted )
Ok, modules loaded: Oops, Whoops.
*Whoops> foo "baz" 7
"(\"baz\",7)"


More information about the Glasgow-haskell-users mailing list