RE: Internal Happy Error

1999-08-02 Thread Simon Marlow

 The following ``code'' forces ghc-4.04 to crash with an
 internal Happy error message:
 
  module Rules where
 
  import GlaExts
  import PrelGHC
 
  integerGcd :: Integer - Integer - Integer
  integerGcd a b
= case a of
(S# a) - case b of
(S# b) - unsafePerformIO $
  _ccall_ gcdSSSZh (I# a) 
 (1::Int) (I# b) = \g -
  case g of (I# g) - return (S# g)
(J# sb b) - unsafePerformIO $
 _casm_ gcdSBSZh a sb b = \g -
 case g of (I# g) - return (S# g)

I get a parse error:

~/scratch  ghc-4.04 test57.lhs -fglasgow-exts  
test57.lhs:14: parse error on input `gcdSBSZh'

it maybe that you compiled up your GHC with an old version of Happy - there
have been several bugfixes in this area in the last few months.

Cheers,
Simon



Re: ghc from CVS (1999/07/31) throws core...

1999-08-02 Thread Marc van Dongen

: Hi!
: 
: I tried to recompile the latest ghc (1999/07/31) on a Linux/glibc2.1.1
: system (egcs 2.91.66), but there seems to be a problem: the build works, but
: the resulting compiler produces executables, that throw core, even with
: "main = return ()".

I've noticed that as well. Code like

does not produce proper error messages anymore which it did with
ghc-4.02. One wonders where the performance boost came from:-)

$ cat tmp.lhs
 module Main( main ) where
 main = putStr $ show q
  where q = quot 1 0
$ ghc-4.02 tmp.lhs
ghc-4.02: module version changed to 176; reason: usages changed
 1006 swift ~/ghc/constraints/mixed
$ a.out

Fail: Prelude.Integral.quot{Integer}: divide by 0
 1007 swift ~/ghc/constraints/mixed
$ ghc-4.04 tmp.lhs
ghc-4.04: module version changed to 177; reason: usages changed
 1008 swift ~/ghc/constraints/mixed
$ a.out
Arithmetic Exception (core dumped)


Regards,


Marc van Dongen



ghc from CVS (1999/07/31) throws core...

1999-08-02 Thread Michael Weber

Hi!

I tried to recompile the latest ghc (1999/07/31) on a Linux/glibc2.1.1
system (egcs 2.91.66), but there seems to be a problem: the build works, but
the resulting compiler produces executables, that throw core, even with
"main = return ()".

I have a CVS version from 1999/07/10, and this one works. I subsequently
recompiled this version with itself several times, no problem.

Since the old version still compiles (I tried this night), and also Manuel
produced a glibc2.1 version of ghc: did anyone change some parts of the rts
or compiler, that could be touchy to specific glibc versions? Or is the
problem related elsewhere?

I wish, I could have provided more debugging info, but strace's and gdb's
output isn't very helpful at all. How do I enable those IF_DEBUG(...) macros
(or something that helps tracking down the problem)? I tried, but it seems I
overlooked something...

However, I "hello-debugged" the problematic version and traced it to
ghc/rts/Schedule.c:

case ThreadEnterGHC:
  ret = StgRun((StgFunPtr) stg_enterStackTop);


The case statement is reached, but then the segmentation fault happens
somewhere in StgRun() or something it calls (*hmm* I don't regard this info
as very helpful at all, since this is pretty early in the startup
process...)


Cheers,
Michael
-- 
* Software Engineering is like looking for a black cat in a dark room in
  which there is no cat.
* Systems Engineering is like looking for a black cat in a dark room in
  which there is no cat and someone yells "I got it!"



Instance declarations get lost from modules imported from absolute paths

1999-08-02 Thread George Russell

The attached tgz archive contains 4 files:
  A.hs defines a type X and a type class Y
  B.hs imports A and makes X an instance of Y
  C.hs imports B and just exports everything again
  D.hs imports C and tries to use the fact that X is an instance of Y.

If you compile this using
  ghc -c [A/B/C/D].hs
then it should all go swimmingly (by the way, we are on Sparc-Solaris and using a 
version
downloaded at the end of last week).

If however you compile it using
  ghc -c [A/B/C/D].hs -i$PWD
(replace $PWD by the absolute path of directory containing A,B,C,D, if your shell 
doesn't)
then it doesn't work.  The reason is that C.hi now only contains the following:

__interface C 1  404 where
__export A X{FOO BAR} Y{p};

where it previously contained

__interface C 1  404 where
__export A X{FOO BAR} Y{p};
import A 1 ::;
import B 1 ! ::;

In other words it looks as if, because A and B were obtained from an absolute path,
ghc has decided to forget to add them to C's import list, so that the instance 
declaration
in B gets lost.

This is really exceptionally confusing.  I am not sure if it is intended or not, but I
certainly don't like it, and it doesn't seem to be documented.  If the use of 
absolute path names for interface files is deprecated then ITWSBT!
 bug.tar.gz


Internal Happy Error (another one)

1999-08-02 Thread Marc van Dongen

Hi there,


ghc-4.04's parser does not seem to like expressions of the following kind:
 case a of
   (#I a) -  
and
 blah (# sa, a, #)

Upon using these expressions it dies due to an internal Happy error.


Hope this helps,



Marc van Dongen



Re: ghc from CVS (1999/07/31) throws core...

1999-08-02 Thread Michael Weber

On Mon, Aug 02, 1999 at 12:54:23 +0100, Marc van Dongen wrote:
[...]
 I've noticed that as well. Code like
 
 does not produce proper error messages anymore which it did with
 ghc-4.02. One wonders where the performance boost came from:-)
 
 $ cat tmp.lhs
  module Main( main ) where
  main = putStr $ show q
   where q = quot 1 0
[...]
 $ a.out
 Arithmetic Exception (core dumped)

Yes, but:

\begin{code}
module Main( main ) where
main = putStr $ show q
 where q = quot 1 (0::Int)
\end{code}
gives: Fail: Prelude.Integral.quot{Int}: divide by 0

IIRC, Integer isn't Div-By-Zero-checked (for performance reasons).

But my core dumps, don't give any "blahblah exception (core dumped)"
messages. The programs just die (at a very early stage). I still think, it's
something with glibc stuff...


Cheers,
Michael
-- 
XXXVI:  The thickness of the proposal required to win a multimillion dollar
contract is about one millimeter per million dollars.  If all the
proposals conforming to this standard were piled on top of each other
at the bottom of the Grand Canyon it would probably be a good idea.



RE: ANNOUNCEMENT: The Glasgow Haskell Compiler, version 4.04

1999-08-02 Thread Simon Marlow


 Why is the parser (parser/Parser.hs) compiled with -H80M? 
 This causes an error
 on my ghc-4.02 (default max heap size 64M). Instead of increasing the
 maximum heap size, I just tried -H64M, which works fine (and 
 it should also
 work without -Hxxx, but it would take probably longer to compile).

It depends on the compiler; 4.02 is pretty hungry and might need more than
64m.

 BTW: Does increasing the default heap size affect the overall memory
 consumption of the compiler?

It shouldn't in general, but it can if your program has strange memory
behaviour.  GHC tries to make best use of all the memory allocated to it by
-H, estimating how the program will behave and sizing the generations
accordingly.  Sometimes the program has a blip in space usage which can
cause GHC to overflow the -H boundary.

Cheers,
Simon



4.02 vs. 4.04 performance figures

1999-08-02 Thread Simon Marlow

Here are the nofib performance results for 4.02 vs. 4.04 if anyone's
interested.

The averages are geometric means across the percentage changes.

Don't pay too much attention to the runtimes, these tend to vary +/- 10% or
so from run to run anyway.

This report is generated by a Haskell program, in case you were wondering
:-)

Cheers,
Simon

--

Binary Sizes


---
Program 4.024.04

---
   HMMS 566k +17.11%
   anna 904k  +0.54%
   ansi 166k -14.96%
 awards 175k  -8.20%
 banner 178k -14.64%
  boyer 162k  -4.93%
 boyer2 191k  -4.90%
   bspt 351k -14.72%
   calendar 158k -15.89%
   cichelli 186k  -7.37%
circsim 277k -16.19%
   clausify 150k  -6.00%
  comp_lab_zift 166k  -1.31%
   compress 213k  +4.18%
  compress2 194k  -7.04%
cse 168k  -2.76%
ebnf2ps 469k  +6.82%
  eliza 187k  -5.53%
  event 139k  -4.90%
 exp3_8 135k  -4.35%
 expert 208k  -8.02%
fem 405k  +2.37%
fft 284k  +6.65%
   fft2 292k +11.94%
   fibheaps 187k  +3.42%
   fish 186k  -1.26%
  fluid 530k  +6.01%
 fulsom 422k  +4.51%
 gamteb 367k +11.06%
gen_regexps 166k  -8.97%
 genfft 147k  -4.18%
 gg 475k  -1.37%
   grep 184k  -2.12%
 hidden 420k  +6.23%
hpg 450k +12.30%
ida 143k  -3.73%
  infer 249k  +9.00%
knights 229k -16.99%
   life 153k -10.94%
   lift 195k  +2.39%
  listcompr 146k  -4.83%
   listcopy 146k  -4.89%
   maillist 174k  -9.98%
 mandel 344k  +6.28%
mandel2 152k  -7.87%
minimax 172k  -8.79%
mkhprog 167k  -2.71%
 multiplier 172k -17.40%
   nucleic2 374k  +3.14%
  paraffins 169k -14.69%
 parser 296k  -1.26%
parstof 286k  +0.97%
pic 367k  +3.48%
 pretty 273k  +9.88%
 primes 129k  -3.14%
  primetest 209k  -2.08%
 prolog 204k  -7.67%
 queens 126k  -3.49%
reptile 329k  -2.78%
rewrite 209k -16.82%
   rfib 257k  +9.37%
rsa 199k  -2.63%
scc 130k  -3.72%
  sched 135k  -3.59%
 simple 499k  -5.03%
  solid 346k  +4.40%
sorting 181k -18.11%
 symalg-   -
tak 139k  -5.18%
  transform 263k  +1.83%
   treejoin 154k  -6.82%
  typecheck 161k  -6.54%
veritas 791k  -2.91%
   wang 275k  +8.20%
  wave4main 160k  +0.40%
   x2n1 269k +12.98%
Average-  -2.85%

Allocations


---
Program 4.024.04

---
   HMMS  exit(1)  

RE: Which GUI on X11R6 ?

1999-08-02 Thread Meurig Sage

Sorry the last time I sent this messed up.

-Original Message-
  Hi,

  has anybody there an idea which GUI is usable with Haskell 98 on
  a Unix/X11R6 system (FreeBSD to be complete)?

As I mentioned in an earlier mail, I'm working on GUIs in Haskell
building on TclHaskell. I'll have a new release of it out in the next
few days that works with hugs98 and ghc-4.04.

Meurig Sage

-- previous mail sent 20 July 1999 --- 

Hi,
I am indeed working on an improved version of TclHaskell. 
I'll be providing an initial release within a few weeks. 
(Hopefully by the end of this month.)

It uses the event and behavior of Fran to allow a more
structured and declarative approach to composing GUIs.

I've also got a modified and patched up version of TclHaskell 
that my stuff is built on top of. I was planning to release
a version of this system as well, to allow several different 
interfaces to access Tcl-Tk from Haskell.

Meurig





Re: Which GUI on X11R6 ?

1999-08-02 Thread Alex Ferguson


Wilhelm B. Kloke:
 has anybody there an idea which GUI is usable with Haskell 98 on
 a Unix/X11R6 system (FreeBSD to be complete)?
 
 It seems that all GUI stuff develepmont (Fudgets, Haggis ...)
 has been stalled since some years.

I'd look at TclHaskell, if I were you.  It's not strictly speaking
under active development or support, as I understand it, but is in
a usable state, and other people seem to be tweaking it, and/or
working on related methodologies.

Cheers,
Alex.





Which GUI on X11R6 ?

1999-08-02 Thread Wilhelm B. Kloke

Hi,

has anybody there an idea which GUI is usable with Haskell 98 on
a Unix/X11R6 system (FreeBSD to be complete)?

It seems that all GUI stuff develepmont (Fudgets, Haggis ...)
has been stalled since some years.

Some of the links in the Haskell libraries and tools page are not even
accessible any more.

If the Win32 API is in better condition, will it be possible to use
this with either Wine or TWIN?

--
Dipl.-Math. Wilhelm Bernhard Kloke
Institut fuer Arbeitsphysiologie an der Universitaet Dortmund
Ardeystrasse 67, D-44139 Dortmund, Tel. 0231-1084-257 montags und dienstags





Re: Which GUI on X11R6 ?

1999-08-02 Thread Thomas Hallgren

"Wilhelm B. Kloke" wrote:

 Hi,

 has anybody there an idea which GUI is usable with Haskell 98 on
 a Unix/X11R6 system (FreeBSD to be complete)?

 It seems that all GUI stuff develepmont (Fudgets, Haggis ...)
 has been stalled since some years.

The fudget library still works and it has actually received various
small improvements and additions over the last couple of years. But this
work has been done as a spare time project and as needed by another
project [1], so we haven't taken the time to create and advertise any
formal releases.

Recent versions of the fudget library and the reference manual
can be found on [2] and [3], respectively. It currently compiles with
HBC for Haskell 1.4 and Haskell 98 and, occasionally also with GHC 4.0x. 

References

[1] http://www.cs.chalmers.se/~hallgren/Alfa/
[2] ftp://ftp.cs.chalmers.se/pub/haskell/chalmers/untested/
[3] http://www.cs.chalmers.se/Cs/Research/Functional/Fudgets/Manual/

--
Thomas Hallgren

PS Since my home computer runs FreeBSD, I know for sure that Fudgets
compiles and runs just fine under FreeBSD :-)