Field label bug?

1999-08-17 Thread Michael Hobbs

Is this a bug with ghc-4.04 or just a "feature" of Haskell 98 that I was
unaware of? I get a parse error with the following code:

data Point = Pt {pointx, pointy :: Float}
abs (Pt {pointx, pointy}) = sqrt (pointx*pointx + pointy*pointy)

It doesn't like the `,' on the second line. If I change it to:

abs (Pt {pointx=pointx, pointy=pointy}) = sqrt (pointx*pointx +
pointy*pointy)

It compiles fine.
This is on Solaris 2.5, in case it matters.

- Michael Hobbs



RE: Problems with GHC 4.04 binary package under i386 Linux

1999-08-17 Thread Simon Peyton-Jones

Simon Marlow is away till next week, so I'm afraid you won't
get any help till then.  Sorry.

Simon

> -Original Message-
> From: Mark Utting 
> Sent: Monday, August 09, 1999 9:49 PM
> To: [EMAIL PROTECTED]
> Cc: [EMAIL PROTECTED]
> Subject: Problems with GHC 4.04 binary package under i386 Linux 
> 
> 
> 
> I am having trouble installing the latest GHC binary bundle for 
> Linux (4.04).  I've tried it under Redhat Linux 5.02, and a
> Slackware Linux distribution (kernel = 2.0.35), with the same results.
> I did not have these problems with GHC 4.02...



Instance bug

1999-08-17 Thread Sven Panne

Here one of my favourite bugs in larger projects (IIRC, this
has partly been reported by me in the "Importing, hiding, and
exporting" thread):

-- A.hs -
module A where
data Foo = Foo -- Typo! Forgot "deriving Show"
-- B.hs -
module B where
import A
data Bar = Bar Foo deriving Show
data Baz = Baz Int deriving Show
-- Main.hs --
import A
import B
main :: IO ()
main = print (Bar Foo, Baz 42)
-

   panne@jeanluc:~ > ghc -Wall -O -c A.hs
   ghc: module version changed to 1; reason: no old .hi file
   panne@jeanluc:~ > ghc -Wall -O -c B.hs
   ghc: module version changed to 1; reason: no old .hi file

[??? Why does B compile? And why is Baz's Show instance not in B.hi? ]

   panne@jeanluc:~ > ghc -Wall -O -c Main.hs

   Main.hs:4:
   No instance for `Show Baz' arising from use of `print' at Main.hs:4

   Main.hs:4:
   No instance for `Show Bar' arising from use of `print' at Main.hs:4

This one drove me mad several times, looking at the completely
wrong place (i.e. B.hs).%-{

Cheers,
   Sven
-- 
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



Typechecker buglet

1999-08-17 Thread Sven Panne

The typo in the following module causes ghc to crash:

--
module Foo where

data Bar = Bar { flag :: Bool }

data State = State { bar :: Bar, baz :: Float }

display :: State -> IO ()
display (State{ bar = Bar { flag = f, baz = b }}) = print (f,b)

-- Typo! The line above should better be:
-- display (State{ bar = Bar { flag = f }, baz = b }) = print (f,b)
--

   panne@jeanluc:~ > ghc -Wall -O -c Foo.hs

   panic! (the `impossible' happened):
   tcLookupValue: b{-r4n-}

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

Done!   :o)

Cheers,
   Sven
-- 
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: Field label bug?

1999-08-17 Thread Michael Weber

On Mon, Aug 16, 1999 at 16:40:30 -0500, Michael Hobbs wrote:
> Is this a bug with ghc-4.04 or just a "feature" of Haskell 98 that I was
> unaware of? I get a parse error with the following code:
> 
> data Point = Pt {pointx, pointy :: Float}
> abs (Pt {pointx, pointy}) = sqrt (pointx*pointx + pointy*pointy)

*hmm* at least hugs also complains:
ERROR "recs.hs" (line 2): Haskell 98 does not support missing field bindings

But you can also do:
\begin{code}
abs (Pt pointx pointy) = sqrt (pointx*pointx + pointy*pointy)
\end{code}
if you don't want to mention field names...


Cheers,
Michael
-- 
Today, signature's out...



(no subject)

1999-08-17 Thread Tim Sauerwein

Hello friends:

Thanks for making GHC available.  I regret to report
the following installation problem.

Yours,
Tim Sauerwein   [EMAIL PROTECTED]

--

Windows 98
Cygwin B20
GHC 4.03, Install Shield Version

Everything unpacked successfully.

Configure produced:

creating cache ./config.cache
checking host system type... i386-unknown-mingw32
checking target system type... i386-unknown-mingw32
checking build system type... i386-unknown-mingw32
Which we'll further canonicalise into: i386-unknown-mingw32
checking for perl... /BIN/perl
checking if `#!/BIN/perl' works in shell scripts
It does!
checking for a BSD compatible install...
/CYGNUS/CYGWIN~1/H-I586~1/BIN/install -c
checking whether ln -s works... yes
checking for sed... /CYGNUS/CYGWIN~1/H-I586~1/BIN/sed
checking for gcc... gcc
checking whether the C compiler (gcc -mno-cygwin  ) works... yes
checking whether the C compiler (gcc -mno-cygwin  ) is a
cross-compiler... no
checking whether we are using GNU C... yes
checking whether gcc accepts -g... yes
checking whether you have an ok gcc... yes
checking how to run the C preprocessor... gcc -E
checking how to invoke GNU cpp directly...
C:/CYGNUS/CYGWIN~1/H-I586~1/BIN/../lib/gcc-lib/i586-cygwin32/egcs-2.91.57/cpp
-iprefix
C:/CYGNUS/CYGWIN~1/H-I586~1/BIN/../lib/gcc-lib/i586-cygwin32/egcs-2.91.57/

updating cache ./config.cache
creating ./config.status
creating Makefile

Configuration done, ready to either 'make install'
or 'make in-place', followed by 'make install-docs'.
(see README and INSTALL files for more info.)


make in-place produced:

make --unix config-pkgs
bindir=/ghc/ghc-4.03/bin/i386-unknown-mingw32/ghc-4.03
libdir=/ghc/ghc-4.03/lib/i386-unknown-mingw32
datadir=/ghc/ghc-4.03/share/ghc-4.03
Configuring ghc, version 4.03, on i386-unknown-mingw32 ...
Creating a configured version of ghc-4.03 ..
cannot create bin/i386-unknown-mingw32/ghc-4.03/ghc-4.03: directory
nonexistent
make[1]: *** [config-pkgs] Error 2
make: *** [in-place] Error 2





RE: Field label bug?

1999-08-17 Thread Simon Peyton-Jones

"Punning" was removed (in my view this was a mistake) in Haskell 98.

That's why neither GHC nor Hugs accepts it.

Simon

> -Original Message-
> From: Michael Hobbs 
> Sent: Monday, August 16, 1999 10:41 PM
> Cc: [EMAIL PROTECTED]
> Subject: Field label bug?
> 
> 
> Is this a bug with ghc-4.04 or just a "feature" of Haskell 98 
> that I was
> unaware of? I get a parse error with the following code:
> 
> data Point = Pt {pointx, pointy :: Float}
> abs (Pt {pointx, pointy}) = sqrt (pointx*pointx + pointy*pointy)
> 
> It doesn't like the `,' on the second line. If I change it to:
> 
> abs (Pt {pointx=pointx, pointy=pointy}) = sqrt (pointx*pointx +
> pointy*pointy)
> 
> It compiles fine.
> This is on Solaris 2.5, in case it matters.
> 
> - Michael Hobbs
>