Using GHC API

Ian Lynagh igloo at earth.li
Sat Nov 25 14:51:29 EST 2006


Hi Chris,

On Fri, Nov 10, 2006 at 04:15:10PM +0000, C.M.Brown wrote:
> 
> I am currently in the process of porting some of the Haskell
> Refactorer (HaRe) over to ghc 6.6. Part of HaRe requires the API and until
> now I've been content with using th 6.5 API. However, since I've started
> the switch I've noticed some strange problems and the latest is I am
> getting the following error when trying to find the type of an expression:
> 
> 
> <interactive>:1:0:
>     Can't find interface-file declaration for Main.main
>       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

Attached is a smaller module showing the same thing, along with the
(trivial) Main.hs I was testing with.

If I tell it to use Interactive mode then all is well:

    $ ./hasktags Interactive Main.hs
    Loading package base ... linking ... done.
    [1 of 1] Compiling Main             ( Main.hs, Main.o )
    Just GHC.IOBase.IO ()

but if I tell it to use JustTypecheck mode then it breaks:

    $ ./hasktags JustTypecheck Main.hs
    [1 of 1] Compiling Main             ( Main.hs, Main.o )
    
    <interactive>:1:0:
        Can't find interface-file declaration for variable Main.main
          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
    Nothing

(remove *.hi *.o between runs)

So it looks like using Interactive mode should allow you to get on for
now.

ghc --show-iface Main.hi gives

    interface main:Main 1 6070 where
    export main:Main main
    module dependencies:
    package dependencies: base
    orphans: base:GHC.Base
    family instance modules:
    main :: GHC.IOBase.IO ()
    main :: GHC.IOBase.IO ()

in the first case, but the last two lines are missing in the second.

This raises a few questions:

Are there meant to be two "main :: GHC.IOBase.IO ()" lines when it works?

Should it work with JustTypecheck? It looks like the point of
JustTypecheck is that IDEs should be able to ask the type of something
actually written in the file, but would it actually be more expensive to
allow the information to be used to type other expressions?

Should JustTypecheck be generating a .hi and .o file at all? It seems
wrong to me.

Simons?


Thanks
Ian

-------------- next part --------------

{-
rm *.o *.hi hasktags
/home/ian/ghc/darcs2/build/compiler/stage2/ghc-inplace --make -package ghc hasktags.hs

rm *.o *.hi
./hasktags Interactive Main.hs

rm *.o *.hi
./hasktags JustTypecheck Main.hs
-}

module Main (main) where

import System (getArgs)

import GHC
import DynFlags (defaultDynFlags)
import Outputable (Outputable, showSDoc, ppr)

ghcPath :: FilePath
ghcPath = "/home/ian/ghc/darcs2/build/inst/lib/ghc-6.7"

main :: IO ()
main = do
  args <- getArgs
  case args of
      "Interactive"  :files -> realMain Interactive   files
      "JustTypecheck":files -> realMain JustTypecheck files

realMain :: GhcMode -> [FilePath] -> IO ()
realMain mode files = defaultErrorHandler defaultDynFlags $ do
    ses <- GHC.newSession mode (Just ghcPath)
    dflags0 <- GHC.getSessionDynFlags ses
    (dflags1,fileish_args) <- GHC.parseDynamicFlags dflags0 []
    GHC.setSessionDynFlags ses $ dflags1 {verbosity = 1}
    targets <- mapM (\a -> GHC.guessTarget a Nothing ) files
    mapM_ (GHC.addTarget ses) targets
    res <- GHC.load ses LoadAllTargets
    ty <- exprType ses "Main.main"
    putStrLn $ showSDoc $ ppr ty 

-------------- next part --------------

module Main (main) where

main :: IO ()
main = return ()



More information about the Glasgow-haskell-users mailing list