[Haskell-cafe] Mutually recursive modules and google protocol-buffers

Sterling Clover s.clover at gmail.com
Tue Jul 15 11:12:51 EDT 2008


What about generating the verbose accessor/single module code, and  
then creating a hierarchical module space as well, all importing your  
Base module, and reexporting the data types you want as well as less  
verbosely named accessor functions? Of course, this will break record  
update syntax, but maybe you could move to functional references  
instead -- given that you're generating all the code to begin with,  
autogenerating fref/lens style getter-setter pairs shouldn't be any  
more work.

--Sterl

On Jul 15, 2008, at 10:43 AM, Chris Kuklewicz wrote:

> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list