[Haskell-cafe] Mutually recursive modules and google
protocol-buffers
Chris Kuklewicz
haskell at list.mightyreason.com
Tue Jul 15 10:43:39 EDT 2008
Ah, a teachable moment. One of us is not entirely correct about what GHC can do
with this example. Hopefully I am wrong, but my experiments...
Max Bolingbroke wrote:
>> And there is no way ghc can compile these in separate modules.
>
> I may be being redundant here, but you may not know that GHC actually
> can compile mutually recursive modules. See
> http://www.haskell.org/ghc/docs/latest/html/users_guide/separate-compilation.html#mutual-recursion
> . Of course, this is not a great solution either, as creating hs-boot
> files is a bit tedious, but at least the option is there.
>
> Cheers,
> Max
Consider these 3 files:
A.hs:
> module A(A) where
> import B(B)
> data A = A B
B.hs
> module B(B) where
> import A(A)
> data B = B A
Main.hs
> module Main where
> import A
> import B
> main = return ()
There is no way to create a "A.hs-boot" file that has all of
(1) Allows A.hs-boot to be compiled without compiling B.hs first
(2) Allows B.hs (with a {-# SOURCE #-} pragma) to be compiled after A.hs-boot
(3) Allows A.hs to compiled after A.hs-boot with a consistent interface
But this "Main2.hs" file works fine:
> module Main where
> data A = A B
> data B = B A
> main = return ()
But in "Main2.hs" I cannot define two record field accessors such as
> data A = A { getName :: B}
> data B = B { getName :: A}
because there cannot be two different "getName" created in the same namespace.
There is no way GHC can put the two field accessors in different module
namespaces because their "data" types include mutual recursion.
So I can choose one of
(*) Ignore mutual recursion and make all such .proto specifications break
(*) Autogenerate very verbose data type names and put them all in the same
module to allow mutual recursion. And then either
(**) Autogenerate even more verbose field accessor names
(**) Define no field accessors and create some poor replacement, such as
> class Field'Name a b | a ->b where
> getName :: a -> b
> setName :: a -> b -> a
Cheers,
Chris
More information about the Haskell-Cafe
mailing list