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.




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



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: 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



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





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 `-Hsize' 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: haskell and exceptions

1998-01-29 Thread Ralf Hinze

Matthias Fischmann writes ...

 I am now trying to learn Haskell for half a week and I like it a lot.
 But I still did not find out too much about exception handling. Is it
 possible that there is no ml-like mechanism with `raise' and `handle'
 built in? Yes, I know about types like
 
 data Result t = ERROR | Yes t
 
 and I also read the chapter in the report about IO, monads, and
 userError. But this seems all a little clumsy compared to the elegant
 and simple exceptions in standard ml or even ugly languages like java.
 
 Did I miss the point? Are there exceptions libraries? Is there any
 extension to Haskell in some existent implementation that handles my
 needs? How do you handle exceptions in your Haskell programs?

No, there are no extensions for handling exceptions. Some may think
that this is a bug but I think it's a feature ;-). First of all it's
against Haskell's spirit of being a pure functional language. Consider

raise First + raise Second handle First = 1 | Second = 2,

what is the value of this expression? It clearly depends on the order
of evaluation. SML defines this rigorously (right?). However, Haskell
is a lazy language, so even if the language designers would undergo
the task of defining the evaluation order, this is nothing which is
easy for the user to understand. 
I usually try to avoid partial functions. That's easier as
one might suppose at first (if one is willing to invent new data types).
Consider operations on priority queues.

 data OptPair a b  =  Null
   |  Pair a b

 class PriorityQueue q where
 empty :: (Ord a) = q a
 meld  :: (Ord a) = q a - q a - q a
 splitMin  :: (Ord a) = q a - OptPair a (q a)

Instead of defining `getMin' and `deleteMin' which are both partial
functions we define `splitMin' which combines both. Here is a simple
application of `splitMin'.

 toOrderedList q   =  case splitMin q of
 Null  - []
 Pair a q  - a : toOrderedList q

For error reporting and alike I usually use an exception
monad.

Hope this helps, Ralf






Re: haskell and exceptions

1998-01-29 Thread Dave Tweed

On Thu, 29 Jan 1998, Ralf Hinze wrote:

 Matthias Fischmann writes ...
 
  I am now trying to learn Haskell for half a week and I like it a lot.
  But I still did not find out too much about exception handling. Is it
  possible that there is no ml-like mechanism with `raise' and `handle'
  built in? Yes, I know about types like
  
  data Result t = ERROR | Yes t
  
  and I also read the chapter in the report about IO, monads, and
  userError. But this seems all a little clumsy compared to the elegant
  and simple exceptions in standard ml or even ugly languages like java.
  
  Did I miss the point? Are there exceptions libraries? Is there any
  extension to Haskell in some existent implementation that handles my
  needs? How do you handle exceptions in your Haskell programs?
 
 No, there are no extensions for handling exceptions. Some may think
 that this is a bug but I think it's a feature ;-). First of all it's
 against Haskell's spirit of being a pure functional language. Consider
 
   raise First + raise Second handle First = 1 | Second = 2,
 
 what is the value of this expression? It clearly depends on the order
 of evaluation. SML defines this rigorously (right?). However, Haskell
 is a lazy language, so even if the language designers would undergo
 the task of defining the evaluation order, this is nothing which is
 easy for the user to understand. 

Don't even more extreme problems with exceptions arise because of lazy io?
E.g., if a function produces a list of integers but can produce an
exception after calculating some of the first elements of the list (say
divide by zero or something), then if this function is used by a lazy
output function (say putStr),
then by the time the exception gets thrown all the elements already
produced will already have been sent to the screen and this can't be
rescinded.

E.g., using the hugs interpreter,

Prelude putStr(show [1/2,2/3,4/0])
[0.5, 0.67,
Program error: {primDivDouble 4.0 0.0}

(Imagine that program error was actually an exception that would be caught
somewhere else.)

In ML the strictness of the language means that this won't happen, and
because it's a functional language there's a guarantee that there are no
`program variables' being corrupted. I'd presume imperative languages like
C++ and java require much more careful, generalised exception planning. (I
don't use C++ exceptions in my programming :-) )

cheers, dave
-
email reply: [EMAIL PROTECTED]   "Life is good for only two things,
http://www.cs.bris.ac.uk/~tweed/discovering mathematics and teaching
work tel: (0117) 9545104mathematics" -- Simeon Poisson






application announce

1998-01-29 Thread S.D.Mechveliani

Announcement:


 The  Algebraic Domain Constructor  DoCon,  version 1.06
 ---


DoCon-1.06
a computer algebra  program  written in a pure functional language 
Haskell (version 1.4)

can be copied freely, as a source program (see license.txt) from

ftp.botik.ru:/pub/local/Mechveliani/docon/1.06/  

--
Abilities (mostly, commutative algebra):

Mathematical library: 
- Linear algebra over a Euclidean domain: reduction to the 
  staircase and diagonal forms of matrix, solving a system,
- Polynomial arithmetic in  R[x1,...,xn],  R a commutative ring, 
- g.c.d in R[x1,...,xn],  R a factorial ring,
- Factorization for the univariate polynomial over a finite 
  field, 
- Groebner basis  and  syzygy generators  in a free module over
  R[x1,...,xn],  R a Euclidean ring;
- Symmetric function package;

Category hierarchy: 
- (static) Set, Semigroup, Group, Ring, SyzygySolvableRing, and 
  so on,
- dynamic Subset, Subgroup, Subring, Ideal, ... operations; 

Functors of the 
- Direct product of the Sets, (semi)Groups, Rings, 
- Matrix algebra over a commutative ring, 
- Polynomial algebra over a commutative ring, 
- Fraction field for a factorial ring, 
- Residue ring;

Property processing:
- the evaluation of certain small set of the most important 
  algebraic property values is supported, such as 
  Finite, IsCyclicGroup, IsMaximalIdeal, etc.
--


For the Haskell language materials, see   http://haskell.org


DoCon-1.06 is a package of the Haskell programs.

It needs theGlasgow Haskell system  ghc-2.10  
- or any higher compatible version 

- for DoCon to be built from the sources and exploited.

ghc  is also freely available with its sources:

  ftp.dcs.gla.ac.uk/pub/haskell/glasgow/
  src.doc.ic.ac.uk/pub/computing/programming/languages/haskell/
  glasgow/

--
DoCon  differs from the most CA programs in that  it  enables  the 
programmer to set the algorithms in the natural and generic mathe-
matical form.
It uses the   categorial approach   to the algebraic computation - 
like the wide-known AXIOM system
(AXIOM is a trademark of the Numerical Algorithms Group Ltd)

- though DoCon has a smaller library of algorithms.

DoCon is pure functional, contains no side effects, and is written
in Haskell only.

To use DoCon-1.06 means to write the programs in Haskell,  compile 
and link them under  ghc  importing object and  interface  modules 
from DoCon-1.06 export directory.

Documentation:  everything is explained in  manual.txt
--

Platforms:
-
DoCon-1.06  has to work everywhere where  ghc-2.10  works (lots of
platforms). 
Though, we have seen it working only on  linux-i386-unknown.
We hope it will install, as it is, on any Unix machine.

And we doubt about  Windows   (if only there exists  ghc-2.10  for
Windows) - the question concerns only the installation Makefile.

Probably, it would not be difficult to port DoCon to other Haskell
implementations: Yale, Chalmers, Hugs, and so on.
And we will be grateful to the users  that  make  DoCon  ports  to
various compilers and environments.


Plans:
--
the future DoCon versions have to implement more  of  mathematics,
use  the  extended  language  tools,  as  the  multiple  parameter
categories and others.
Also the  contributions  are welcome.

The known  *bugs* and their walk-arounds  are listed in
   ftp.botik.ru:/pub/local/Mechveliani/docon/1.06/bugs.txt

The remarks are welcome:   [EMAIL PROTECTED]



Sergey D.Mechveliani
senior researcher,
Program Systems Institute, 152140, Pereslavl-Zalessky, Russia.
e-mail  [EMAIL PROTECTED]
phone   +7(08535)98022