Meaning of -i and -hidir

Domínguez, Facundo facundo.dominguez at tweag.io
Fri Oct 22 16:16:28 UTC 2021


Dear devs,

I'm confused about the meaning of -hidir and -i. Here's my experiment with
both ghc-9.2.0 and ghc-8.10.4.

> $ find
> ./Main.hs
> ./lib/Lib.hs
>
> $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib
>
> $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main
>
> Main.hs:3:1: error:
>     Bad interface file: hidir_Main/Lib.hi
>         hidir_Main/Lib.hi: openBinaryFile: does not exist (No such file
or directory)
>   |
> 3 | import Lib
>   | ^^^^^^^^^^

If I only use -hidir, it still fails with another error

> $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib
>
> Main.hs:7:29: error: Variable not in scope: f
>   |
> 7 | main = print $(runIO (print f) >> [| True |])
>   |                             ^

If I use both -i and -hidir pointing to the same folder, then it works!

> $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib

Now, is this behavior a bug or a feature? And if it is a bug, what is the
expected behavior?

Programs copied below.

Thank you!
Facundo

> $ cat lib/Lib.hs
> module Lib where
>
> f :: Int
> f = 1
>
> $ cat Main.hs
> {-# LANGUAGE TemplateHaskell #-}
>
> import Lib
> import Language.Haskell.TH <http://language.haskell.th/>
>
> main :: IO ()
> main = print $(runIO (print f) >> [| True |])
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20211022/d1335af9/attachment.html>


More information about the ghc-devs mailing list