.hi-boot abuse
George Brewster
brewster at post.harvard.edu
Sat Dec 6 13:30:24 EST 2003
Hi,
I have a question which came up as a result of some attempts to enforce
seperate compilation. Suppose we have two modules as follows:
------ A.hs --------
module A (AbstractType) where
data AbstractType = it's hidden implementation
f :: AbstractType -> String
f _ = "foo"
g :: AbstractType
g = something
------ B.hs ---------
module B where
import A
s = f g
Now, I want to be able to Compile A, Compile B, change the
implementation of AbstractType in A, recompile A, and then not have to
recompile B. Unfortunately, this doesn't seem to happen in GHC 6.0.1, as
the representation of AbstractType is placed in A.hi, so when the
representation changes, it forces a recompilation of B.
In order to get seperate compilation, we tried abusing the .hi-boot
mechanism by writing A.hi-boot and changing the "import A" in B.hs to
"import {-# SOURCE #-} A":
------- A.hi-boot -------
module A where
data AbstractType
f :: AbstractType -> GHC.Base.String
g :: AbstractType
This, scarily enough, accomplishes what we want (forcing AbstractType to
be very abstract, so changes to it don't require recompilation of B),
but could lead to some evil breakage if A.hi-boot doesn't match A.
At first glance, it seems like it wouldn't be too hard to have the
compiler do a consistency check between A.hs and A.hi-boot when A is
compiled, which would make this safe (assuming that compiling B using
only A.hi-boot is safe if A.hi-boot is consistent with A...).
Thus, it seems like the hi-boot mechanism could be extended to allow
programmers the option of manually writing interfaces to reduce compile
dependencies between modules. Certainly this would come at some cost in
performance, but it seems like a useful tradeoff to allow.
Is this reasonable?
-George Brewster
More information about the Glasgow-haskell-users
mailing list