Re: Fun with 3.00

1998-01-29 Thread Simon L Peyton Jones

> One can play funny games with GHC-3.00 and the following program
> (a small fragment of a Happy-generated parser):
> 
> --
> module Foo ( happyParse ) where
> 
> action_0 1 = \j tk _ -> action_1 j j tk (HappyState action_1)
> 
> action_1 3 = error "Bar"
> action_1 _ = \i tk st@(HappyState action) sts stk -> action (-1) (-1) tk st sts 
>(Just i : stk)
> 
> happyParse = action_0 2 2 '-' (HappyState action_0) [] [] 2
> 
> newtype HappyState b c =
>HappyState (Int -> Int -> b -> HappyState b c -> [HappyState b c] -> c)
> --

Great program!  Thanks for isolating it.

Simon: pls add to regression suite

There are two problems.  One is a long-standing bit of grubbiness
in the code generator; hence fun_result_ty panic.  I've fixed that
(still grubbily, I fear).

GHC goes into a loop in the update analyser.  Reason: the 
recursive contravariance of HappyState.  Consider:

action_1 j j tk (HappyState action_1) sts stk
= {unfold action_1}
action_1 (-1) (-1) tk (HappyState action_1) sts (Just j:stk)
= {unfold action_1 again}
... 

Neither action_0 nor action_1 is recursive, but infinite unfolding
can still occur.  This can cause the simplifier to loop, though
on this occasion it doesn't, but only because action_1 is
considered too big to unfold.  But it does make the update analyser
loop, for some obscure reason.  It wouldn't surprise me if the
strictness analyser looped too, but it doesn't.

For some reason there's no flag to switch off the update analyser.
It does very little good anyway, so just switch it off by force
in ghc/driver/ghc.lprl (look for -fupdate-anal).

I've known about the possibility of looping in the simpifier for some time, but
never seen it in a real program.  I have no idea how to spot it in a clean way,
and without disabling lots of useful inlining.  (I prevent looping mainly by
treating letrec carefully.)  Ideas welcome

Simon





Re: error: (misc)

1998-01-29 Thread Sigbjorn Finne



Alex Ferguson writes:
> 
> install-sh does a fine line in unhelpful error messages: well, error
> message singular, at any rate...
> 
> for i in hp2ps; do \
> /export/home/ferguson/ghc-3.00/build/install-sh -c  -g ghc-admin   -s $i 
> /usr/local/bin; \
> done
> hp2ps:error reading file
> 
> This seems to be its catch-all for anything that goes wrong, making
> diagnosis a tad tricky.  On one machine it was a full disk, another
> one I'm still trying to puzzle out...
> 

install-sh is the fallback script used if the configure script is
unable to find an OK looking `install' somewhere along your PATH.
If install-sh is such a pain to work with, you may want to try
out the `install' that comes with the GNU fileutils.

--Sigbjorn



Fun with 3.00

1998-01-29 Thread Sven Panne

One can play funny games with GHC-3.00 and the following program
(a small fragment of a Happy-generated parser):

--
module Foo ( happyParse ) where

action_0 1 = \j tk _ -> action_1 j j tk (HappyState action_1)

action_1 3 = error "Bar"
action_1 _ = \i tk st@(HappyState action) sts stk -> action (-1) (-1) tk st sts (Just 
i : stk)

happyParse = action_0 2 2 '-' (HappyState action_0) [] [] 2

newtype HappyState b c =
   HappyState (Int -> Int -> b -> HappyState b c -> [HappyState b c] -> c)
--

  * Compiling it as-is with "ghc-3.00 -O -c Foo.hs" yields:
=> panic! (the `impossible' happened):
fun_result_ty: 6 PrelBase.Int{-3f-}
 -> PrelBase.Int{-3f-}
 -> b_tr74
 -> Foo.HappyState{-r6P-} b_tr74 c_tr75
 -> [Foo.HappyState{-r6P-} b_tr74 c_tr75]
 -> c_tr75

  Please report it as a compiler bug to [EMAIL PROTECTED]

  * If newtype is changed to data or "( happyParse )" is deleted,
it compiles fine.

  * GHC-2.10 doesn't complain in any way.

  * If the first equation of action_1 is commented out, GHC seems to loop:
ghc-3.00 -O -c Foo.hs -H50M -K50M
=> GHC's heap exhausted;
   while trying to allocate 20 bytes in a 5000-byte heap;
   use the `-H' option to increase the total heap size.

Cheers,
   Sven "Unhappy-too" Panne

-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



Re: Buggy derived instance of Show

1998-01-29 Thread Sigbjorn Finne


Manuel Chakravarty writes:
> 
> I found a bug in derived instances for Show that contain
> `Float' numbers.  Running
> 
>   data MassPnt  = MassPnt Float (Float, Float)
> deriving (Show)
> 
>   main = do
>  print 1.18088e+11
>  let p = MassPnt 1.18088e+11 (-0.768153, -0.742202)
>  print p
> 
> the first `print' is successfully executed, but the attempt
> to output `1.18088e+11' below the constructor `MassPnt'
> fails with
> 
>   Fail: Char.intToDigit: not a digit
> 

Hi,

thanks for a fine report ( `main=print (1.18088e+11 :: Float)' is the
shortest example that shows this one up.)

The bug is due to wonky tests for exceptional IEEE float values,
something that wasn't caught by our regression tests. 

The attached patch should apply to ghc-2.02/2.03 sources or later.

--Sigbjorn



*** ghc/lib/cbits/floatExtreme.lc.~1~   1997/05/18 04:26:47
--- ghc/lib/cbits/floatExtreme.lc   1998/01/29 13:39:58
***
*** 7,10 
--- 7,15 
  source.
  
+ ToDo:
+   - avoid hard-wiring the fact that on an
+ Alpha we repr. a StgFloat as a double.
+ (introduce int equivalent of {ASSIGN,PK}_FLT? )
+ 
  \begin{code}
  
***
*** 81,96 
  }
  
  StgInt
  isFloatNaN(f) 
  StgFloat f;
  {
! int ix;
  int r;
  
! ix = (int)f;
! ix &= 0x7fff;
! ix = 0x7f80 - ix;
! r = (int)(((unsigned int)(ix))>>31);
  return (r);
  }
  
--- 86,108 
  }
  
+ /* Same tests, this time for StgFloats. */
+ 
  StgInt
  isFloatNaN(f) 
  StgFloat f;
  {
! #if !defined(alpha_TARGET_OS)
! /* StgFloat = double on alphas */
! return (isDoubleNaN(f));
! #else
! union { StgFloat f; int i; } u;
  int r;
+ u.f = f;
  
! u.i &= 0x7fff;
! u.i = 0x7f80 - u.i;
! r = (int)(((unsigned int)(u.i))>>31);
  return (r);
+ #endif
  }
  
***
*** 99,108 
  StgFloat f;
  {
  int ix;
  
! ix = (int)f;
! ix &= 0x7fff;
! ix ^= 0x7f80;
! return (ix == 0);
  }
  
--- 111,126 
  StgFloat f;
  {
+ #if !defined(alpha_TARGET_OS)
+ /* StgFloat = double on alphas */
+ return (isDoubleInfinite(f));
+ #else
  int ix;
+ union { StgFloat f; int i; } u;
+ u.f = f;
  
! u.i &= 0x7fff;
! u.i ^= 0x7f80;
! return (u.i == 0);
! #endif
  }
  
***
*** 111,119 
  StgFloat f;
  {
! int high, iexp;
  
! high = (int)f;
! iexp = high & (0xff << 23);
  return (iexp == 0);
  }
  
--- 129,143 
  StgFloat f;
  {
! #if !defined(alpha_TARGET_OS)
! /* StgFloat = double on alphas */
! return (isDoubleDenormalized(f));
! #else
! int iexp;
! union { StgFloat f; int i; } u;
! u.f = f;
  
! iexp = u.i & (0xff << 23);
  return (iexp == 0);
+ #endif
  }
  
***
*** 122,127 
  StgFloat f;
  {
! int high = (int)f;
! return (high == 0x8000);
  }
  
--- 146,158 
  StgFloat f;
  {
! #if !defined(alpha_TARGET_OS)
! /* StgFloat = double on alphas */
! return (isDoubleNegativeZero(f));
! #else
! union { StgFloat f; int i; } u;
! u.f = f;
! 
! return (u.i  == (int)0x8000);
! #endif
  }


]



Re: Strange module exportation behavior

1998-01-29 Thread Simon L Peyton Jones


Conal: great bug report; thanks.  Meanwhile a workaround is
to use qualified names in the export list for Test2:

module Test2( Test1.foo, module Test2 )
  import Test1 hiding(main)
  main = ...

Inconvenient, but it should get you rolling.  

Simon, Sigbjorn: I've fixed this and checked in the changes (in rename/..).
Conal will need a new build in due course.

Simon

> I'm getting strange behavior from both GHC and Hugs w.r.t. module
> exportations.  They disagree with each other somewhat and both seem wrong,
> although I'm not certain I understand the report on this matter.
> 
> Here are two test programs.  First Test1.hs:
> 
> module Test1 (module Test1) where
> main = putStrLn "Test1's main"
> foo = "Test1 foo"
> 
> In Test2.hs, I want to modify and extend Test1, keeping "foo" but
> replacing main.
> 
> module Test2 (module Test1, module Test2) where
> import Test1 hiding (main)
> main = putStrLn "Test2's main"
> bar = foo ++ " plus Test2 bar"





Re: That's "ghc-3.00", please!

1998-01-29 Thread Simon Marlow

Alex Ferguson <[EMAIL PROTECTED]> writes:

> Hi again.  I note in passing that ghc still installs itself as "ghc",
> not as "ghc-[version]" (with ghc as a link).  At least two of the
> Si*o*n-Squad -- that was a regular expression, not an expletive deleted ;-)
>  -- have been promising that this will be/has been fixed in the next
> version for several versions now!

I must admit, I don't trust 'make install' at all, and generally tend
to 'make binary-dist' and install that instead.  I'm actually quite
surprised that you only had that one problem :-)  

As for fixing it, I thought I did, but must have forgotten to check it
in.  Sorry about that.

Cheers,
Si\(gbjor|mo\)n

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: GHC-3.00 on Linux an HP

1998-01-29 Thread Simon Marlow

Sven Panne <[EMAIL PROTECTED]> writes:

>* On HPs (and presumably any machine without a native code generator)
>  building hsc failed:
> 
> /soft/bin/ghc -O -H32m -DOMIT_NATIVE_CODEGEN -cpp -fglasgow-exts 
>-Rghc-timing -I. -IcodeGen -InativeGen -Iparser -iutils:basicTypes:types:hsSyn:prel
> 
>ude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser
> -recomp -c absCSy
> n/CLabel.lhs -o absCSyn/CLabel.o -osuf o
>  
> absCSyn/CLabel.lhs:315: Value not in scope: `fmtAsmLbl'
>  
> absCSyn/CLabel.lhs:319: Value not in scope: `underscorePrefix'

Thanks - I fixed this in another branch and forgot to bring it over.

>* The syntax error at "make install"-time is due to a (cut-and-paste?)
>  bug in the Makefile:



>* The configure script of a binary distribution should not only tell
>  you to do a "make install", but a "make install-docs", too.
>  This is easily forgotten.

Well spotted, will do.

Many thanks for the builds, I'll point to them from our download
page.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: Build glitch in hslibs/contrib

1998-01-29 Thread Simon Marlow

Jeff Lewis <[EMAIL PROTECTED]> writes:

> The Makefile in hslibs/contrib tries to expand the heap for Cubic_Spline
> by setting:
> Cubic_Spline_HC_OPTS=-H10m
> This relies on
> HC_OPTS = ... $($*_HC_OPTS) ...
> However, since the source file is in the subdirectory src, $* gets
> expanded to `src/Cubic_Spline', instead of the intended `Cubic_Spline',
> the end result being that ghc bails out with the dreaded
> GHC's heap exhausted!

Thanks - I found this this morning after the overnight builds failed.
Not sure how it got there - it probably wasn't noticed because I'm
lazy and always use GhcLibHcOpts=-H25m or something.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Still unhappy

1998-01-29 Thread Ralf Hinze

> Guess what?  It's the old 'for i in ;' problem again.  Try 'make
> install SHELL=bash' (I think the upper case is important).

Yes, the upper case is important. However, installing happy from the
binaries still does not work. Here is a summary of my undertakings:

gunzip < happy-1.5-sparc-sun-solaris2.tar.gz | tar -xf -
mkdir fptools.sparc
cd fptools.sparc
lndir ../fptools .
./configure --prefix=$HOME/FP/ghc
creating ./config.status
creating Makefile
**
Configuration done, ready to either 'make install'
or 'make in-place'.
(see README and INSTALL files for more info.)
**
gold 958> make install SHELL=bash
Configuring happy, version 1.5, on sparc-sun-solaris2 ...
rehash
happy
/home/III/a/ralf/FP/ghc/bin/happy: /home/III/a/ralf/FP/ghc/lib/happy-1.5/happy.bin: 
not found

Any suggestions, Ralf



GHC-3.00 on Linux an HP

1998-01-29 Thread Sven Panne

A few glitches of the latest-and-greatest GHC:

   * On HPs (and presumably any machine without a native code generator)
 building hsc failed:

/soft/bin/ghc -O -H32m -DOMIT_NATIVE_CODEGEN -cpp -fglasgow-exts -Rghc-timing 
-I. -IcodeGen -InativeGen -Iparser -iutils:basicTypes:types:hsSyn:prel

ude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser
 -recomp -c absCSy
n/CLabel.lhs -o absCSyn/CLabel.o -osuf o
 
absCSyn/CLabel.lhs:315: Value not in scope: `fmtAsmLbl'
 
absCSyn/CLabel.lhs:319: Value not in scope: `underscorePrefix'

 My guess/hack:

*** fptools/ghc/compiler/absCSyn/CLabel.lhs.~1~ Thu Jan  8 19:03:24 1998
--- fptools/ghc/compiler/absCSyn/CLabel.lhs Thu Jan 29 09:35:08 1998
***
*** 67,72 
--- 67,77 
  import Unique ( showUnique, pprUnique, Unique{-instance Eq-} )
  import Util   ( assertPanic{-, pprTraceToDo:rm-} )
  import Outputable
+ 
+ #if OMIT_NATIVE_CODEGEN
+ underscorePrefix = False
+ fmtAsmLbl x = x
+ #endif
  \end{code}
  
  things we want to find out:
-

   * The syntax error at "make install"-time is due to a (cut-and-paste?)
 bug in the Makefile:

-
diff fptools/distrib/Makefile-bin.in{.~1~,}
126,127c126,127
<   for i in $(PACKAGE_PRL_SCRIPTS) ""; do \
<@if test "$(PACKAGE_PRL_SCRIPTS)"; then \
---
>   @for i in $(PACKAGE_PRL_SCRIPTS) ""; do \
>if test "$$i"; then \
143,144c143,144
<   for i in $(PACKAGE_LIB_PRL_SCRIPTS) ""; do \
<@if test "$(PACKAGE_LIB_PRL_SCRIPTS)"; then \
---
>   @for i in $(PACKAGE_LIB_PRL_SCRIPTS) ""; do \
>if test "$$i"; then \
160,161c160,161
<   for i in $(PACKAGE_SH_SCRIPTS) ""; do \
<@if test "$(PACKAGE_SH_SCRIPTS)"; then \
---
>   @for i in $(PACKAGE_SH_SCRIPTS) ""; do \
>if test "$$i"; then \
-

   * The configure script of a binary distribution should not only tell
 you to do a "make install", but a "make install-docs", too.
 This is easily forgotten.

   * Building info files still doesn't work. But this is a known bug in
 sgml-tools-1.0.3.

The Linux version is ready at:

   
ftp://ftp.informatik.uni-muenchen.de/pub/local/pms/ghc-3.00-all-i386-unknown-linux.tar.gz

A HP version will be there soon. Because of some HP-magic they will be
statically linked. Just a few 100kBs more and hopefully no more errors
from the dynamic linker...

-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



ghc-3.00/irix build problem

1998-01-29 Thread Fuad Abdallah

Hi,

compiling the ghc-3.00 source for irix 6.2 fails with the following error:

in ghc/runtime:

../../ghc/driver/ghc -I../includes -optc-DGCap   -O -optc-DIN_GHC_RTS=1
-I../runtime/storage   -optc-DIN_GHC_RTS=1  -c main/StgStartup.hc -o
main/StgStartup.o -osuf o
main/StgStartup.hc:232: warning: assignment makes integer from pointer
without a cast
Prologue junk?: .entArrayOfData_entry
ArrayOfData_entry:
#.file  1 "main/StgStartup.hc"
.frame  $sp,2168,$31
.mask   0x9000,-4
.fmask  0x,0
.mask   0x8000,-16
sd  $31,0($sp)


I assume this is based on the new gcc version i have installed here.
gcc-2.8.0 does not support the old irix binary format (o32) but produces
the new 32 Bit (n32) and the 64Bit (64) output (and the assembler format
has changed)
I have started to rebuild most of the libs on my machine in 64 Bit and of
course would like to build a 64 Bit version of ghc. I have appended the
output of gcc -mabi=64 -S test-arch.c (from ghc/misc) and would be pleased
if someone could have a look at the irix port (the gcc call in the ghc
driver would have to be changed to 'gcc -mabi=64' to produce 64 bit
output). 

If it helps i could setup an account here (if have been reading you have
no irix 6. box around).  

regards,
Fuad




#.file  1 "test-arch.c"
.option pic2
.section.text
.text
.align  2
.globl  foo
.entfoo
foo:
.frame  $fp,112,$31 # vars= 64, regs= 3/0, args= 0, extra= 16
.mask   0xd000,-16
.fmask  0x,0
dsubu   $sp,$sp,112
sd  $31,96($sp)
sd  $fp,88($sp)
sd  $28,80($sp)
move$fp,$sp
.setnoat
lui $1,%hi(%neg(%gp_rel(foo)))
addiu   $1,$1,%lo(%neg(%gp_rel(foo)))
daddu   $gp,$1,$25
.setat
sd  $4,16($fp)
s.d $f13,24($fp)
sd  $6,32($fp)
sd  $7,40($fp)
s.d $f16,48($fp)
sd  $9,56($fp)
move$2,$10
sd  $11,72($fp)
sb  $2,64($fp)
 #APP
--- BEGIN ---
 #NO_APP
ld  $3,40($fp)
lbu $2,0($3)
l.d $f1,24($fp)
cvt.s.d $f0,$f1
move$4,$2
mov.s   $f13,$f0
ld  $6,16($fp)
ld  $7,56($fp)
ld  $8,40($fp)
ld  $9,40($fp)
dla $25,bar
jal $31,$25
 #APP
--- END ---
 #NO_APP
.L1:
move$sp,$fp
ld  $31,96($sp)
ld  $fp,88($sp)
ld  $28,80($sp)
daddu   $sp,$sp,112
j   $31
.endfoo
.align  2
.globl  bar
.entbar
bar:
.frame  $fp,96,$31  # vars= 48, regs= 3/0, args= 0, extra= 16
.mask   0xd000,-16
.fmask  0x,0
dsubu   $sp,$sp,96
sd  $31,80($sp)
sd  $fp,72($sp)
sd  $28,64($sp)
move$fp,$sp
.setnoat
lui $1,%hi(%neg(%gp_rel(bar)))
addiu   $1,$1,%lo(%neg(%gp_rel(bar)))
daddu   $gp,$1,$25
.setat
move$2,$4
s.s $f13,20($fp)
sd  $6,24($fp)
sd  $7,32($fp)
sd  $8,40($fp)
sd  $9,48($fp)
sb  $2,16($fp)
 #APP
--- BEGIN ---
 #NO_APP
l.s $f1,20($fp)
cvt.d.s $f0,$f1
lbu $2,16($fp)
ld  $4,24($fp)
mov.d   $f13,$f0
move$6,$0
ld  $7,40($fp)
dmtc1   $0,$f16
ld  $9,32($fp)
move$10,$2
ld  $11,32($fp)
dla $25,foo
jal $31,$25
 #APP
--- END ---
 #NO_APP
.L2:
move$sp,$fp
ld  $31,80($sp)
ld  $fp,72($sp)
ld  $28,64($sp)
daddu   $sp,$sp,96
j   $31
.endbar
.align  2
.globl  baz
.entbaz
baz:
.frame  $fp,4048,$31# vars= 4016, regs= 2/0, args= 0, extra= 16
.mask   0x5000,-8
.fmask  0x,0
dsubu   $sp,$sp,4048
sd  $fp,4040($sp)
sd  $28,4032($sp)
move$fp,$sp
.setnoat
lui $1,%hi(%neg(%gp_rel(baz)))
addiu   $1,$1,%lo(%neg(%gp_rel(baz)))
daddu   $gp,$1,$25
.setat
sw  $4,16($fp)
sw  $0,4024($fp)
.L4:
lw  $2,4024($fp)
slt $3,$2,1000
bne $3,$0,.L7
b   .L5
.L7:
lw  $2,4024($fp)
li  $3,4# 0x0004
mult$2,$3
daddu   $2,$fp,24
mflo$6
dsll$6,$6,32
dsrl$6,$6,32
mfhi$7
dsll$7,$7,32
or  $7,$7,$6
daddu   $3,$2,$7
lw  $2,16($fp)
lw  $3,0($3)
addu$2,$2,$3

Re: Floats don't like to be referenced [was: Buggy derived instance of Show]

1998-01-29 Thread Jon Mountjoy



Manuel Chakravarty writes:
 > Scary, but true...the floats in my version of ghc don't like 
 > to be referenced.  The program
 > 
 >   data MassPnt  = MassPnt Float (Float, Float)
 >deriving (Show)
 > 
 >   main = do
 > print 1.18088e+11-- (1)
 > let 
 >   x = 1.18088e+11
 >   p = MassPnt x (-0.768153, -0.742202)   -- (*)
 > print x  -- (2)
 > 
 > prints `1.18088e+11' successfully at line (1), but fails in
 > line (2) with `Fail: Char.intToDigit: not a digit'.

The problem persists in GHC-2.10 and GHC-3.00 (which, by the way, was
a dream to install except for the Cubic Spline problem noted before).

Jon



Build glitch in hslibs/contrib

1998-01-29 Thread Jeff Lewis

The Makefile in hslibs/contrib tries to expand the heap for Cubic_Spline
by setting:
Cubic_Spline_HC_OPTS=-H10m
This relies on
HC_OPTS = ... $($*_HC_OPTS) ...
However, since the source file is in the subdirectory src, $* gets
expanded to `src/Cubic_Spline', instead of the intended `Cubic_Spline',
the end result being that ghc bails out with the dreaded
GHC's heap exhausted!

--Jeff



Floats don't like to be referenced [was: Buggy derived instance of Show]

1998-01-29 Thread Manuel Chakravarty

Scary, but true...the floats in my version of ghc don't like 
to be referenced.  The program

  data MassPnt  = MassPnt Float (Float, Float)
  deriving (Show)

  main = do
   print 1.18088e+11-- (1)
   let 
 x = 1.18088e+11
 p = MassPnt x (-0.768153, -0.742202)   -- (*)
   print x  -- (2)

prints `1.18088e+11' successfully at line (1), but fails in
line (2) with `Fail: Char.intToDigit: not a digit'.

But now the *interesting* part: When I remove the line (*),
everything works just fine!  Floats just don't like to be
referenced...or is there not enough space allocated for them
in the heap and they tend to be overwritten?

Now, I don't have the lattest version of GHC, so maybe
someone else hit that problem earlier (I also did't follow
all discussions on this list).  (As said earlier, I used ghc
2.05 on Linux 2.0.30.) 

Manuel

P.S.: Of course, I think that the problem that I reported
  earlier was actually caused by the above one.




Buggy derived instance of Show

1998-01-29 Thread Manuel Chakravarty

Dear GHC Bug Hunters,

I found a bug in derived instances for Show that contain
`Float' numbers.  Running

  data MassPnt  = MassPnt Float (Float, Float)
  deriving (Show)

  main = do
   print 1.18088e+11
   let p = MassPnt 1.18088e+11 (-0.768153, -0.742202)
   print p

the first `print' is successfully executed, but the attempt
to output `1.18088e+11' below the constructor `MassPnt'
fails with

  Fail: Char.intToDigit: not a digit

The program doesn't fail for all floating point numbers,
e.g., `0.0' is output without any problems.  I used

  ghc 2.05 on Linux 2.0.30

Actually, I am pretty sure that this is not the whole story,
because I also had problems applying `show' directly to some
floating point numbers.  But, I couldn't reproduce this in a
small example yet.

Manuel