Haddock can't parse data declaration involving operator

2004-05-09 Thread Stefan Reich
Hi,

I hope this is the right place to ask about Haddock problems?

I'm using Haddock 0.6 (RedHat RPM module) under RedHat 9. When I invoke 
haddock on this file (Op.hs):

	module Op where

infixl 4 :=
data a := b = a := b
I get the error Op.hs:Illegal data/newtype declaration.

Is this a known problem?

Asking more broadly - maybe there is another tool that does what I need: 
I just want an overview of all my modules including their exported 
identifiers and all type signatures (including inferred signatures).

Thanks in advance,
-Stefan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Two problems with heap profiling

2004-05-09 Thread Stefan Reich
Yes, same thing here on RedHat 9... apparently a problem specific to the 
Windows port.

-Stefan

Sven Panne wrote:

Stefan Reich wrote:

[...] The program crashes every time I run it (Windows XP this time, but
I assume that doesn't make a difference).


Hmmm, it works with GHC 6.2.1 and the one from the HEAD on my x86 Linux 
box.
Perhaps something WinDoze-related, I don't know = SimonM...

Cheers,
   S.



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


What happened to constrFields?

2004-05-09 Thread Stefan Reich
In recent versions of the GHC libraries, constrFields (as defined here 
http://www.cs.vu.nl/boilerplate/library/Data.Generics.Basics.html) has 
disappeared. I failed to figure out another way to get the names of all 
fields of a constructor.

Have I overlooked anything? Do I have to use Template Haskell?

-Stefan

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: What happened to constrFields?

2004-05-09 Thread Ralf Laemmel
The problem is that constrFields is not included with 6.2.1.
You would need to build GHC from CVS.
It will be in 6.4 for sure.
And yes, you are right, there is no other way to get the names
of all fields of a constructor.
Ralf

Stefan Reich wrote:

In recent versions of the GHC libraries, constrFields (as defined here 
http://www.cs.vu.nl/boilerplate/library/Data.Generics.Basics.html) has 
disappeared. I failed to figure out another way to get the names of 
all fields of a constructor.

Have I overlooked anything? Do I have to use Template Haskell?

-Stefan

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Prelude/main magicks?

2004-05-09 Thread Niklas Broberg
Hello, fellow GHCees,

I am currently co-developing a language[1] as an extension to Haskell, by 
means of a preprocessor to GHC. In this language we want to supply the 
programmer with a number of functions by default, as with the functions in 
the GHC Prelude.
Is there some simple way to make GHC treat our own base library in the same 
magic way as the Prelude, so that it is always implicitly available? Note 
that we don't want to exchange the existing Prelude for our own, we want to 
leave that one as it stands, rather we want one or more other libraries to 
be treated the same way as the Prelude.
If the answer is no, that cannot be done, I would humbly request this as a 
feature in upcomming versions of GHC, I believe it's generally useful 
feature to have. =)

And while I'm asking about magicks; In our language we have a special 
function, called page, that we require be present in executable modules, 
much like a main-function. Once again, is there some way of tweaking GHC to 
check this for us? We cannot simply use a 'main-is' flag since this function 
is not executed the same way that a main function would be, and its type 
should not be IO ().
I don't expect to be able to tell GHC what function must have what type with 
a command line flag, but is there some other way?

Any leads are appreciated, even if they only lead into the source code of 
GHC...

/Niklas Broberg

[1] Haskell Server Pages: http://www.dtek.chalmers.se/~d00nibro/hsp/

_
The new MSN 8: advanced junk mail protection and 2 months FREE* 
http://join.msn.com/?page=features/junkmail

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Prelude/main magicks?

2004-05-09 Thread Tomasz Zielonka
On Sun, May 09, 2004 at 06:54:27PM +, Niklas Broberg wrote:
 I am currently co-developing a language[1] as an extension to Haskell, by 
 means of a preprocessor to GHC. In this language we want to supply the 
 programmer with a number of functions by default, as with the functions in 
 the GHC Prelude.
 Is there some simple way to make GHC treat our own base library in the same 
 magic way as the Prelude, so that it is always implicitly available?

Perhaps your preprocessor could just place a suitable 'import' in the
generated Haskell module?

 And while I'm asking about magicks; In our language we have a special 
 function, called page, that we require be present in executable 
 modules, much like a main-function. Once again, is there some way of 
 tweaking GHC to check this for us?

Along the same lines: put something like this in the generated module

  requirePage :: ()
  requirePage = f page
where
  f :: PageType - ()
  f _ = ()

IIRC if you use a name beginning with underscore, GHC won't warn that it
is unused.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Prelude/main magicks?

2004-05-09 Thread Tomasz Zielonka
On Sun, May 09, 2004 at 09:45:32PM +0200, Tomasz Zielonka wrote:
 
   requirePage :: ()
   requirePage = f page
 where
   f :: PageType - ()
   f _ = ()

Or simpler:

_requirePage :: PageType
_requirePage = page

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Prelude/main magicks?

2004-05-09 Thread Niklas Broberg
 I am currently co-developing a language[1] as an extension to Haskell, 
by
 means of a preprocessor to GHC. In this language we want to supply the
 programmer with a number of functions by default, as with the functions 
in
 the GHC Prelude.
 Is there some simple way to make GHC treat our own base library in the 
same
 magic way as the Prelude, so that it is always implicitly available?

Perhaps your preprocessor could just place a suitable 'import' in the
generated Haskell module?
Indeed, and that is precisely what we are doing right now. And it's not 
really all that much work for us either, but I can envision other uses for 
such a feature as well, so my question still stands.

 And while I'm asking about magicks; In our language we have a special
 function, called page, that we require be present in executable
 modules, much like a main-function. Once again, is there some way of
 tweaking GHC to check this for us?
Along the same lines: put something like this in the generated module

  requirePage :: ()
  requirePage = f page
where
  f :: PageType - ()
  f _ = ()
Hmm, this is an interesting idea. I see a problem though, since (just like 
with main) we don't require just all modules to contain such a function, 
only the executable ones. That would correspond to the one that we invoke 
ghc (with the preprocessor) on, but ghc in turn will invoke the preprocessor 
on all modules that are loaded. In other terms, ghc can know which module is 
the first, but the preprocessor has no idea.

Thanks for the input,

/Niklas

_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users