compiler bug in ghc-2.02

1997-04-22 Thread Meurig Sage

When compiling the following program, the compiler
crashed with a bug. This only happens when compiling
with -O.

--
module Test where
import GlaExts
test :: PrimIO ()
test = ioToPrimIO (putStr "bob") `seqPrimIO` test
--

--
ghc-2.02 -O -c test.hstest.hs:8: 
Warning: Possibly incomplete patterns
in a group of case alternatives beginning: 1 -> ...

*** Pattern-matching error within GHC!

This is a compiler bug; please report it to [EMAIL PROTECTED]

Fail: "coreSyn/CoreUtils.lhs", line 122: pattern-matching failed in case
-

I'm using ghc-2.02, with the i386-unknown-solaris2
pre-built distribution.

Cheers,
  Meurig



ghc-2.02 linux binary difficulties

1997-04-22 Thread Tim Pollitt


The heading is 'difficulties', since I'm not confident about distiguishing
between bugs and effects of user obtusity - I'll leave it to you to decide if
any of the following behaviours are unintended.  

Environment: Linux 2.0.0, Gcc 2.7.2, Perl 5.003
Distribution: ghc-2.02-i386-unknown-linux (2nd version? ie. hbc libs incl)

1.  Install guide 4.3: ".. will also make a link (in the binary installation
directory) from ghc to ghc-2.02."  In my /usr/local/bin I find ghc-2.02
is a link to ghc. I'm confused. (But then I'm often confused by links,
usually when creating them.)  What will 2.03 install do?  Overwrite the
previous driver script, then leave all version links pointing to new ghc?

2.  Announce: ".. incompletely supported, notably polymorphic strictness
annotations.."  I'd hoped this referred only to constructor flags, since
2.01 doc was a little more explicit about seq/strict (User 12.5:
".. strict function doesn't really do what you want either.")
   
FEB page, Wrong type for seq: ".. serious, albeit advertised, shortcoming
.." suggests to me that there is some documentation I've overlooked.
Could you please point me to any discussion of this - especially work-
arounds - since a working strict is crucial for programs which accumulate
results over long lazy lists.
The code below 

> strict' f x = if (x == x) then f x else error "{strict': ... huh ?}"
> foldl' f a [] = a
> foldl' f a (x:xs) = strict' (foldl' f) (f a x) xs
> main = do l <- getLine
>   print $ foldl' (+) 0 [ 1 | i <- [0..read l] ]

seems to work, since input of 100 no longer blows the default stack
allocation, but of course strict' has type Eq a => ... cf. Eval a => ...
If I give foldl' an explicit general type

> foldl' :: Eq a => (a -> b -> a) -> a -> [b] -> a

the program will now blow the default heap allocation, for same input.
Why?

3.  Even the tiny program above, when compiled with '-O', elicits:
"NOTE: simplifier still going after 4 iterations; bailing out".
User 3.9, Known troublespots, says ".. please report it as a bug .."

4.  Next para. in Known troublespots describes undefined *_vap_info symbols
as "very unlikely".  Will this one go away soon, without additional source
examples?  (My code is: (a) embarrassingly ugly; (b) a bit sensitive -
part of an attempt to induce a company to consider Haskell as a 
prototyping tool.)

5.  Not Linux any more, but now i386-unknown-cygwin32 binary distr:
'make install' bombs trying to copy hp2ps, until I just remove it from
PACKAGE_BINS.  Perhaps to do with differing executable suffixes under
Win32; I didn't look any further since I wouldn't willingly develop in
such a flaky environment, but needed to confirm that it is possible.

6.  Not a bug at all, but a query related to the previous item:
superficial reading of Install guide suggests that building a cross-
compiler is catered for; are there any complications, especially for
the unix-host/Win32-target case?

Thanks for the fun tool,
TWP  



Re: Haskell compiler

1997-04-22 Thread Simon L Peyton Jones


| From: Janos Blazi <[EMAIL PROTECTED]>
| Date: Sun, 13 Apr 1997 16:17:56 +0200
| Hallo!
| 
| I teach at a German grammar school and Haskell would be a wonderful =
| language for teaching Infomation Technologies. But I think istallation =
| is hopeless for a UNIX-illiterate like me. (I use NT 4.0.)

Have you considered using Hugs?  It's much easier to install, and being
interactive it's better for teaching.
http://www.haskell.org/
Simon



Re: problem with syslib hbc and Time in ghc-2.02

1997-04-22 Thread Sigbjorn Finne


Meurig Sage writes: 
> I tried compiling a program using -syslib hbc, I
> wanted Random.lhs, but I required the standard Time library
> aswell. Unfortunately there's an interface file for hbc called
> Time.hi, that overrides the haskell 1.4 Time library. I assume this
> just requires renaming of some of the hbc stuff.

Hi,

thanks for the report - we've encountered the exact same problem with
2.02; fixed in 2.03 (hbc library is renamed to TimeUtil).

--Sigbjorn