[Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Roman Cheplyaka
I wonder whether it's always possible to break cycles using GHC's
.hs-boot files.

Consider the following schematic example:

  module A where

  import B

  data A

  f :: B - A
  f = undefined B.g

  module B where

  import A

  data B

  g :: A - B
  g = undefined A.f

A.hs-boot must give a type signature for f, and since the signature
contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
'A'.

Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
between the hs-boot files.

So, am I right in understanding that these recursive modules cannot be
compiled by GHC at all?

Roman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Francesco Mazzoli
At Wed, 8 May 2013 09:46:08 +0300,
Roman Cheplyaka wrote:
 
 I wonder whether it's always possible to break cycles using GHC's
 .hs-boot files.
 
 Consider the following schematic example:
 
   module A where
 
   import B
 
   data A
 
   f :: B - A
   f = undefined B.g
 
   module B where
 
   import A
 
   data B
 
   g :: A - B
   g = undefined A.f
 
 A.hs-boot must give a type signature for f, and since the signature
 contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
 'A'.
 
 Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
 between the hs-boot files.
 
 So, am I right in understanding that these recursive modules cannot be
 compiled by GHC at all?

This configuration works for me:

A.hs:

module A where
import B

data A

f :: B - A
f = undefined B.g

A.hs-boot:

module A where

import {-# SOURCE #-} B

data A

f :: B - A

B.hs:

module B where
import {-# SOURCE #-} A

data B

g :: A - B
g = undefined A.f

B.hs-boot:

module B where
data B

Then I can compile them:

bitonic@clay /tmp % ghc -c B.hs-boot
bitonic@clay /tmp % ghc -c A.hs-boot
bitonic@clay /tmp % ghc -c B.hs 
bitonic@clay /tmp % ghc -c A.hs 

Francesco

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutually recursive modules

2013-05-08 Thread Roman Cheplyaka
Ah yes, thank you!

* Francesco Mazzoli f...@mazzo.li [2013-05-08 08:51:12+0100]
 At Wed, 8 May 2013 09:46:08 +0300,
 Roman Cheplyaka wrote:
  
  I wonder whether it's always possible to break cycles using GHC's
  .hs-boot files.
  
  Consider the following schematic example:
  
module A where
  
import B
  
data A
  
f :: B - A
f = undefined B.g
  
module B where
  
import A
  
data B
  
g :: A - B
g = undefined A.f
  
  A.hs-boot must give a type signature for f, and since the signature
  contains 'B', it must import 'B'. Ditto for B.hs-boot — it must import
  'A'.
  
  Even if we treat all imports as {-# SOURCE #-}, there is still a cycle
  between the hs-boot files.
  
  So, am I right in understanding that these recursive modules cannot be
  compiled by GHC at all?
 
 This configuration works for me:
 
 A.hs:
 
 module A where
 import B
 
 data A
 
 f :: B - A
 f = undefined B.g
 
 A.hs-boot:
 
 module A where
 
 import {-# SOURCE #-} B
 
 data A
 
 f :: B - A
 
 B.hs:
 
 module B where
 import {-# SOURCE #-} A
 
 data B
 
 g :: A - B
 g = undefined A.f
 
 B.hs-boot:
 
 module B where
 data B
 
 Then I can compile them:
 
 bitonic@clay /tmp % ghc -c B.hs-boot
 bitonic@clay /tmp % ghc -c A.hs-boot
 bitonic@clay /tmp % ghc -c B.hs 
 bitonic@clay /tmp % ghc -c A.hs 
 
 Francesco

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mutually recursive modules

2009-02-06 Thread Henning Thielemann


I have written a small overview, how mutually recursive modules are 
currently supported and how they can be avoided:

  http://haskell.org/haskellwiki/Mutually_recursive_modules

Please add information about other compilers and more ideas on breaking 
cycles.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-16 Thread Chris Kuklewicz

Thanks Roberto!

Roberto Zunino wrote:

Chris Kuklewicz wrote:

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


I thought the following A.hs-boot would suffice:

module A(A) where
data A

There's no need to provide the data constructors for type A. Does this 
violate any of the goals above?


Regards,
Zun.



I tried that experiment.  The failure is complicated, and triggers be a ghc bug.

Hmmm... the bug for


module A(A) where
data A
  deriving Show


using ghc -c -XGeneralizedNewtypeDeriving A.hs-boot is


A.hs-boot:2:0:ghc-6.8.3: panic! (the 'impossible' happened)
  (GHC version 6.8.3 for powerpc-apple-darwin):
newTyConEtadRhs main:A.A{tc r5z}

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug


Is this a known bug?

But now I see that


module A(A(..)) where
import B(B)
data A = A B | End
  deriving Show



does work.  And avoids the bug!

--
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-16 Thread Sittampalam, Ganesh
Hi,

 module A(A) where
 data A
   deriving Show

I think you should use instance Show A rather than deriving Show.
All the boot file needs to do is say that the instance exists, not
explain how it is constructed.

Cheers,

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Chris Kuklewicz

I have reached an impasse in designing a Haskell API for the google's
protocol-buffers data language / format. (
http://code.google.com/apis/protocolbuffers/docs/overview.html )

The messages in protobuf are defined in a namespace that nests in the usual
hierarchical OO style that Java encourages.

To avoid namespace conflicts, I made a hierarchy of modules.

But...this is a legal pair protobuf message definitions:


// Test that mutual recursion works.
message TestMutualRecursionA {
  optional TestMutualRecursionB b = 1;
  optional int32 content = 2;
}

message TestMutualRecursionB {
  optional TestMutualRecursionA a = 1;
  optional int32 content = 2;
}


And there is no way ghc can compile these in separate modules.

But the overlap of record accessors names content makes defining these
messages in a single module with a common namespace quite verbose.

Any opinions on the least worst way to design this?

--
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Max Bolingbroke
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Chris Kuklewicz
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Henning Thielemann


On Tue, 15 Jul 2008, Chris Kuklewicz wrote:


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 ()



Sooner or later you want generalize your datatypes. Then you can define
   data A b = A b
  and you do not need to import B any longer. I do not know if this is a 
generally applicable approach, but it helped me in some cases.
 There is still a problem with mutually recursive classes. In the one case 
where I had this problem, I could solve it the opposite way, namely by 
turning one type variable into a concrete type, which could represent all 
values one could represent with the variable type.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Roberto Zunino

Chris Kuklewicz wrote:

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


I thought the following A.hs-boot would suffice:

module A(A) where
data A

There's no need to provide the data constructors for type A. Does this 
violate any of the goals above?


Regards,
Zun.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Sterling Clover
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Stuart Cook
On Wed, Jul 16, 2008 at 12:54 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:
 Sooner or later you want generalize your datatypes. Then you can define
   data A b = A b
  and you do not need to import B any longer. I do not know if this is a
 generally applicable approach, but it helped me in some cases.

This only really works if it's natural for A to be polymorphic in b.
Otherwise you end up with all sorts of irrelevant administrative type
parameters polluting your signatures.

(I recently had a similar problem with mutually recursive modules; I
ended up deciding to write my program in not-Haskell instead, which
made me a little sad.)


Stuart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread John Meacham
On Tue, Jul 15, 2008 at 12:21:16PM +0100, Chris Kuklewicz wrote:
 I have reached an impasse in designing a Haskell API for the google's
 The messages in protobuf are defined in a namespace that nests in the usual
 hierarchical OO style that Java encourages.

 To avoid namespace conflicts, I made a hierarchy of modules.

I wonder if this is the root of your issue, OO concepts don't map
directly to haskell concepts a lot of the time. You may end up with some
very atypical haskell code if you try to copy OO designs directly. 

John 

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-07-15 Thread Jason Dusek
John Meacham [EMAIL PROTECTED] wrote:
 Chris Kuklewicz wrote:
  I have reached an impasse in designing a Haskell API for the
  google's The messages in protobuf are defined in a namespace
  that nests in the usual hierarchical OO style that Java
  encourages.

  To avoid namespace conflicts, I made a hierarchy of modules.

 I wonder if this is the root of your issue, OO concepts don't
 map directly to haskell concepts a lot of the time. You may
 end up with some very atypical haskell code if you try to copy
 OO designs directly.

  What do you think is a good approach to a protocol buffer
  parser generator?

-- 
_jsn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mutually Recursive Modules

2008-06-02 Thread Richard Giraud

Hello

I'm using GHC 6.8.2 with mutally recursive modules.  I'm familiar with 
how to do simple cases in GHC ({-# SOURCE #-} and .hs-boot files) but I 
can't figure out how to get it to work for a particular set of modules.


Is it known (i.e., proven) that GHC 6.8.2 can compile any set of 
mutually recursive modules without refactoring?  Are there known 
limitations?


Thanks,

Richard G.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutually Recursive Modules

2008-06-02 Thread Isaac Dupree

Richard Giraud wrote:

Hello

I'm using GHC 6.8.2 with mutally recursive modules.  I'm familiar with 
how to do simple cases in GHC ({-# SOURCE #-} and .hs-boot files) but I 
can't figure out how to get it to work for a particular set of modules.


Is it known (i.e., proven) that GHC 6.8.2 can compile any set of 
mutually recursive modules without refactoring?  Are there known 
limitations?


With the old (6.2 and before) .hi-boot scheme where there was no 
abstraction in boot-files, it could probably do anything that it could 
do.  But I'm not convinced with .hs-boot... it can resolve one level of 
cycle, and I don't know how to *prove* that it *can't* do any given 
thing, but I strongly suspect there are things it can't do.  Luckily, it 
is very often the case that your code will be better off anyway if 
refactored to have less module recursion. (though not always.)


-Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mutually Recursive Modules

2008-06-02 Thread ajb

G'day all.

Quoting Isaac Dupree [EMAIL PROTECTED]:


Luckily,
it is very often the case that your code will be better off anyway if
refactored to have less module recursion. (though not always.)


Nonetheless, I prefer not to leave the robustness of my code to luck.
Besides, if I liked structuring code around artificial language
restrictions, I'd be programming in C, not Haskell.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-27 Thread Andrew Pimlott
On Mon, Sep 27, 2004 at 10:46:25AM -0700, Fergus Henderson wrote:
   (2) Although most of the mutual recursion occurred only in the
   intermediate stages of the refactoring, some of the mutual
   recursion remained at the end of the refactoring, forcing
   two modules with only the smallest degree of coupling to be
   combined into a single module.
   
 The two modules in question were (a) the module which defines
 the calling interface between the Cryptol front-end and the
 various Cryptol back-ends, and (b) the module which defines the
 structure which records the settings of command-line options.
 Here (a) depends on (b) because one of the parameters which
 is passed to the back-ends is the command-line option settings,
 and (b) depends on (a) because one of the option settings is
 the currently selected back-end (represented using an
 existentially quantified typeclass-constrained type).

As a programmer not necessarily speaking about Haskell, I also find that
mutually dependent modules are often natural in practice, and that
avoiding them requires excessive and awkward factoring.  Eg, a
configuration module C and a database module D, in which D depends on C
because the configuration contains the database to use, and C depends on
D because configuration data (other than which database to use!) can
come from the database.

I think that on principle, haskell implementors should not doubt that
programmers will find good use for mutually recursive modules if they
are available in a convenient form.

Andrew
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] mutually recursive modules

2004-09-24 Thread Henning Thielemann

As far as can see neither Hugs or GHC really support them. Is this still
on the to-do list or is it almost dropped due to implementation
difficulties? 


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Henning Thielemann

On Fri, 24 Sep 2004, Malcolm Wallace wrote:

 Hugs doesn't support mutually-recursive modules at all.  Ghc and nhc98
 support them only if you hand-write a .hi-boot file to bootstrap the
 compilation.  I would guess that better support from the mainstream
 implementations is unlikely, because it would be a large amount of
 effort for a situation which occurs only very rarely, and for which
 there is a relatively easy workaround.

Namely? The only workaround I know of is putting all type declarations and
functions that depend on each other into one module, import them in the
modules they logically belong to and document that the objects should be
imported from the redirecting modules rather than from the modules they
are defined in.
 I know of two projects where different tasks had to be merged into one
module because of the lack of mutually recursive imports, namely
functionalMetaPost and Haskore.
 It's interesting how other languages solve this problem. In Modula-3 it
is solved by explicit module interfaces and partial revelation. One can
define type T in module A and type T in module B very abstractly as
pointers to something and the complete data structures (which may contain
references to either interface) are usually revealed in the
implementations of the modules. I'm curious how Oberon solves it, because
it doesn't need explicit interfaces but derives them from the
implementation files. Probably one can say that Oberon extracts something
like a .hiboot file from every module file automatically. Why can't GHC
and Hugs go this way?


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Malcolm Wallace
Henning Thielemann [EMAIL PROTECTED] writes:

 As far as can see neither Hugs or GHC really support them. Is this still
 on the to-do list or is it almost dropped due to implementation
 difficulties? 

Hugs doesn't support mutually-recursive modules at all.  Ghc and nhc98
support them only if you hand-write a .hi-boot file to bootstrap the
compilation.  I would guess that better support from the mainstream
implementations is unlikely, because it would be a large amount of
effort for a situation which occurs only very rarely, and for which
there is a relatively easy workaround.

Some lesser-known Haskell implementations do fully support
mutually-recursive modules however.  hhc (formerly Freja, from
Henrik Nilsson) allows multiple modules to be stored in a single
file, and hence mutual recursion can be achieved by ensuring all the
recursive modules are compiled simultaneously from the same file.
The PacSoft Haskell system (from the Programatica project at OGI)
also fully supports mutually recursive modules, and I believe they
can even be in separate files.

Regards,
Malcolm
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Malcolm Wallace
Henning Thielemann [EMAIL PROTECTED] writes:

 a situation which occurs only very rarely, and for which
  there is a relatively easy workaround.
 
 Namely? ...

See below.

  It's interesting how other languages solve this problem. In Modula-3 it
 is solved by explicit module interfaces and partial revelation.

Essentially this is how ghc and nhc98 solve it too.  You must write
an explicit module interface (the .hi-boot file).  This is the
easy workaround.  One benefit of these systems over Modula is that
you /only/ need to write explicit interfaces where there is module
recursion - in all non-recursive contexts, the interface generation
is automatic.

 I'm curious how Oberon solves it, because
 it doesn't need explicit interfaces but derives them from the
 implementation files. Probably one can say that Oberon extracts something
 like a .hiboot file from every module file automatically. Why can't GHC
 and Hugs go this way?

The main obstacle is that Haskell systems generally process one
file/module at a time.  To extract an interface from each module
first, before further processing, would not only require a second
pass over the source files, but to load all of them simultaneously,
which can be rather space-hungry.

Anyway, as Diatchki, Jones, and Hallgren [1] have demonstrated,
it is certainly possible to build a Haskell compiler that deals
properly with recursive modules.

Regards,
Malcolm

[1] Iavor S. Diatchki, Mark P. Jones, and Thomas Hallgren
A Formal Specification for the Haskell 98 Module System
ACM Haskell Workshop, 2002, Baltimore
http://www.cse.ogi.edu/~diatchki/hsmod/

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Alastair Reid
The original Haskell design included interface files usually with names like 
Main.hi

IIRC, Yale Haskell expected them to be hand-written while HBC and GHC 
machine-generated but allowed the careful user to write them by hand.
Sometime around Haskell 1.4 or 98, they were dropped because Yale Haskell had 
died and there seemed little point in specifying the format of 
machine-generated files.

(Hugs' support for modules was added long after the original Hugs design - it 
was hard getting it to do as much as it does.  At one point, I almost had it 
supporting mutually recursive modules but I couldn't quite get all the 
dependencies in the typechecker under control so I settled for just 
supporting module namespaces and qualifiers.)

It is _almost_ possible to generate .hiboot files automatically.  If you see a 
data declaration in the .hs file, copy it to the .hiboot file, if you see a 
function prototype, copy it, etc.  That is, you generate a .hiboot file by 
just deleting all function definitions.

One of the tedious bits is that that you need to do a tricky least fixpoint 
calculation just to figure out what is exported by a set of mutually 
recursive modules if they each reexport their imports.  

Generating .hiboot files by just deleting function definitions fails if there 
is no prototype for an exported function.  A crude approach is to assume the 
type (\forall a. a) for any function with no prototype but, although this is 
sound (I think), it will cause valid programs to be rejected.  This problem 
could be overcome by specifying it as the correct behaviour :-) (Is it sound 
to use (\forall a. a) in the presence of higher-kinded types and all those 
other extensions?)

Hmmm, maybe someone familiar with the Haskell-source libraries could quickly 
hack up a program to generate .hiboot files automatically and make it 
available - that would quickly find the issues (and also identify any 
weaknesses in ghc's error checking of .hiboot files :-).

--
Alastair Reid

  It's interesting how other languages [handle mutually recursive modules]
  problem. In Modula-3 it is solved by explicit module interfaces and
  partial revelation. One can 
 define type T in module A and type T in module B very abstractly as
 pointers to something and the complete data structures (which may contain
 references to either interface) are usually revealed in the
 implementations of the modules. I'm curious how Oberon solves it, because
 it doesn't need explicit interfaces but derives them from the
 implementation files. Probably one can say that Oberon extracts something
 like a .hiboot file from every module file automatically. Why can't GHC
 and Hugs go this way?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Andreas Rossberg
Alastair Reid wrote:
Generating .hiboot files by just deleting function definitions fails if there 
is no prototype for an exported function.  A crude approach is to assume the 
type (\forall a. a) for any function with no prototype but, although this is 
sound (I think), it will cause valid programs to be rejected.
Huh? How can that ever be sound? Are you sure you didn't mean (\exists a.a)?
- Andreas
--
Andreas Rossberg, [EMAIL PROTECTED]
Let's get rid of those possible thingies!  -- TB
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Henning Thielemann

On Fri, 24 Sep 2004, Malcolm Wallace wrote:

 The main obstacle is that Haskell systems generally process one
 file/module at a time.  To extract an interface from each module
 first, before further processing, would not only require a second
 pass over the source files, but to load all of them simultaneously,
 which can be rather space-hungry.

I don't see where it is necessary to load more modules than usually. 
Modula doesn't support cycles in the dependencies. Each implementation
depends only on interfaces of other modules and the interfaces must not
depend cyclicly. Haskell compilers can reduce the problem to the situation
of Modula by extracting the interface from the implementation. Maybe it's
better if the user explicitly allows mutually recursive modules with a
command line option which will invoke an automatic interface generation.
The generation of an interface file should depend only on the
corresponding implementation file, as it is the case for manual .hiboot
creation.  For mutually recursive functions across modules the signature
had to be specified by the user to avoid the simultaneous loading of all
modules. 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Jan-Willem Maessen
An anecdotal note -

hbcc (the front end to the pH and Eager Haskell compilers, and also of
GRIN) contained several mutually recursive modules both in the compiler
and in the prelude.

One of the best things we ever did was get rid of the mutual recursion. 
The resulting refactoring helped us to group related pieces which had
(for historical reasons) ended up scattered.  It also cut our rebuild
time dramatically, and let us do cross-module inlining and optimization
safely.

In short, using mutual recursion was probably a bad idea, and we found
we were better off without it.

-Jan-Willem Maessen

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread Alastair Reid
Alastair:
 A crude approach is to assume the type (\forall a. a) for any
 function with no prototype  

Andreas:
 Huh? How can that ever be sound?

You're right, it's not - my mistake.

I guess that leaves two options:

1) Insist on a prototype for any exported function.
2) Insist on a prototype for any imported function which is used.

The latter is more in keeping with Haskell's lazy checking of import clashes.

(There's a third option where you assume a type which you don't know anything 
about like (\exists a. a) but I'd be surprised if this let you typecheck any 
more useful programs.)

--
Alastair
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread ajb
G'day all.

Quoting Henning Thielemann [EMAIL PROTECTED]:

 Why can't GHC and Hugs go this way?

As Alastair noted, the problem is that Haskell allows you to export
symbols from a module whose types are unknown unless you type-check
modules that it imports.  Simple example:

 module A where
 import B
 a = b

 module B where
 import A
 b = a

This is only a problem for exported symbols which have no type
declarations.  As Alastair said:

 I guess that leaves two options:

 1) Insist on a prototype for any exported function.
 2) Insist on a prototype for any imported function which is used.

 The latter is more in keeping with Haskell's lazy checking of import clashes.

That's true, but you have to ask why you're exporting a function if
you're not going to use it.  On the other hand, in the presence of
Haskell's export everything feature, it makes a certain amount of
sense.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe