Incorrect parse errors

2001-12-11 Thread Ian Lynagh


Hiyas


With the module

{
 main = undefined
 foo = 5
}

and with the module

module Foo where {
 foo = 5
 bar = 6
}

I get

tt.hs:4: parse error on input `='


Thanks
Ian


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Incorrect parse errors

2001-12-11 Thread Simon Peyton-Jones

quite right too.  The explicit { suppress the implicit layout.

Simon

| -Original Message-
| From: Ian Lynagh [mailto:[EMAIL PROTECTED]] 
| Sent: 11 December 2001 13:20
| To: [EMAIL PROTECTED]
| Subject: Incorrect parse errors
| 
| 
| 
| Hiyas
| 
| 
| With the module
| 
| {
|  main = undefined
|  foo = 5
| }
| 
| and with the module
| 
| module Foo where {
|  foo = 5
|  bar = 6
| }
| 
| I get
| 
| tt.hs:4: parse error on input `='
| 
| 
| Thanks
| Ian
| 
| 
| ___
| Glasgow-haskell-bugs mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-bugs
| 

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: Incorrect parse errors

2001-12-11 Thread Ian Lynagh

On Tue, Dec 11, 2001 at 06:10:11AM -0800, Simon Peyton-Jones wrote:
 quite right too.  The explicit { suppress the implicit layout.

Yes, sorry, my bad.


IAn


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



ANN: GHC 5.02.1 RPMs including xlib and HGL packages

2001-12-11 Thread Manuel M. T. Chakravarty

The following might be of special interest to people who are
using Paul Hudak's Haskell textbook for teaching and or
study and would like to run the SOE graphics examples with
GHC - or if you simply want to have an X-based graphics
library for an application.

GHC's source distribution contains the two library packages
`xlib' and `HGL' (Alastair Reid's Haskell Graphics Library)
as part of hslibs, which are not by default built and
installed.  For our local teaching needs at the University
of New South Wales, we have produced a patched version of
GHC 5.02.1 that includes the aforementioned libraries in a
working form.  Haskell modules can be compiled or linked
against these libraries, by providing the command line
options `-package xlib' and `-package HGL', respectively (or
you can specify them using the :s command in the
interpreter).

RPM packages for x86 GNU/Linux based on glibc 2.2 (eg,
RedHat 7.x) containing GHC 5.02.1 including the xlib and HGL
packages are available as

ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-5.02.1-graphics.1.i386.rpm
ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-prof-5.02.1-graphics.1.i386.rpm
ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-doc-5.02.1-graphics.1.i386.rpm

with the source RPM at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/ghc-5.02.1-graphics.1.src.rpm

The source RPM contains a patched source tar ball and build
instructions in the form of an RPM .spec that may be used to
build the packages for other Linux distributions and on
other Unix systems.  (NB: GreenCard need not be installed to
build this package, as a throw-away version of GreenCard is
included in the tar ball - ie, it is used in the build
process, but not installed.)

Cheers,
Manuel

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



FW: Clarification of \begin{code} ... \end{code} stuff

2001-12-11 Thread Simon Peyton-Jones

 In the thread Literate scripts not handled correctly Simon Marlow
 said:
 
  Yes, it looks like GHC's unlit program removes whitespace when 
  looking for \begin{code}, but not for \end{code}.  The report isn't 
  explicit about whether whitespace is allowed on these lines, but I 
  would tend to the view that it isn't.
 
 Can you please clarify this in the report [...]

I'm sure the \begin{code} and \end{code} should
be at the beginning of a line.   Whether anything else should be allowed
on that line is moot.  Maybe not.   What would the layout be for this?
\begin{code} f x = x
\end{code}

On the other hand it would be painful if a block of code was omitted
because
of a trailing space on the \begin{code} line; an easy error.

I therefore propose code starts on the line *following* a line beginning
with \begin{code}.  And similarly stops on a line beginning \end{code}.

For Ian's snippet:

\begin{code}

foo = hello\
\end{code}

\end{code}

I think it's clear that the first \end{code} should be scanned as part
of the string literal.

Simon


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



GCD

2001-12-11 Thread Simon Peyton-Jones

About the GCD operator, the Haskell Report currently says:

gcd x y is the greatest integer that divides both x and y. 
lcm x y is the smallest positive integer that both x and y divide.

Why does 'lcm' say 'positive' while 'gcd' does not?  What is

gcd -3 -6

Presumably 3, not -3.   You could say that is obvious, since 3  -3.

So I propose to add positive to the gcd spec:

gcd x y is the greatest POSITIVE integer 
that divides both x and y. 

I don't think that changes the specification in fact, but experience
has led me to always check these things!

Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GCD

2001-12-11 Thread Ch. A. Herrmann

 Simon == Simon Peyton-Jones [EMAIL PROTECTED] writes:


Simon  gcd x y is the greatest POSITIVE integer that divides
Simon both x and y.

Simon I don't think that changes the specification in fact, but
Simon experience has led me to always check these things!

I find it confusing to read a definition which contains redundant
information. Instead, I'd suggest to add something like:

  Note: this number is always positive

Cheers
-- 
 Christoph Herrmann

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Instance declarations and class exports

2001-12-11 Thread Simon Peyton-Jones

Folks,

Iavor has made two excellent points, upon which I have been
ruminating (and consulting).  Consider

module Foo( M.Ix( index ) ) where
  import qualified Ix as M( Ix )
  import qualified Ix as T( index )

  instance M.Ix MyType where
index a = ...

  index v = ... -- A local declaration

Notice that:
  * The Ix class is in scope as M.Ix, but
its index method is in scope ias T.index.  

  * Nevertheless, it's 100% clear what we mean in the
instance declaration

  *  It's also 100% clear what we mean in the export list
M.Ix( index )
 (The report is currently silent about whether this is legal.)

  * These two situations are very similar, and should be 
resolved in the same way

   * I think we all agree that it woudl be illegal to mention
the 'range' method of the Ix class, either in the
instance cecl, or in theexport list.
Why?  Because 'range' is not imported.


I therefore want to propose:

1.  subordinate names in export lists are always unqualified
Thus, we can have M.Ix( index ), but not M.Ix( T.index ).

2.  A subordinate name in an export list is legal if the entity (class
operation or data constructor) is in scope in the module, regardless
of whether it is in scope under a qualified or unqualified name.  
(In the example, T.index.)

3.  The exact same rule is used to determine whether the class method
name on the LHS of an instance-decl binding is legal.


This time I have implemented the rule first, and it seems fine.

These are basically clarifications.   Objections?  Comments?
I'd like to find a better wording for (2) above.

Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



haxml

2001-12-11 Thread David Smallwood


Does anyone know of a mirror site where I can download the latest
version of HaXml.  (Connection to York is - and has been for a
while - apparently down:  ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/HaXml-1.02.tar.gz, 
that is)

Many thanks

d.
--
David Smallwood 
Dept. of  Computing Science 
De Montfort University  
The Gateway 
Leicester LE1 9BH, UK   
[EMAIL PROTECTED]   

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GCD

2001-12-11 Thread John Meacham

On Tue, Dec 11, 2001 at 11:06:28AM +0100, Ch. A. Herrmann wrote:
  Simon == Simon Peyton-Jones [EMAIL PROTECTED] writes:
 Simongcd x y is the greatest POSITIVE integer that divides
 Simon both x and y.
 
 Simon I don't think that changes the specification in fact, but
 Simon experience has led me to always check these things!
 
 I find it confusing to read a definition which contains redundant
 information. Instead, I'd suggest to add something like:
 
   Note: this number is always positive

yeah. I strongly agree with this wording. precision without confusion is
a really nice feature in specifications. mainly i know that if i were to
read the redundant version I would invariably spend several brain cycles
trying to figure out why it isn't redundant, only to conclude that it
is.
John

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GCD

2001-12-11 Thread S.M.Kahrs

The natural reading of 'greatest' is, of course,
the greatest in the divisibility preorder (it's partial order
on natural numbers but only a preorder on integers).
Thus, gcd 0 0 = 0.

3 and -3 are equivalent in that preoder.

Thus, an additional comment may be in order.

Stefan

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GCD

2001-12-11 Thread Keith Wansbrough

 Simongcd x y is the greatest POSITIVE integer that divides
 Simon both x and y.
 
 I find it confusing to read a definition which contains redundant
 information. Instead, I'd suggest to add something like:
 
   Note: this number is always positive

Or, perhaps easier on the eye,

  gcd x y is the greatest (positive) integer that divides both x and y.

--KW 8-)

-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Instance declarations and class exports

2001-12-11 Thread Simon Peyton-Jones

|  1.  subordinate names in export lists are always 
| unqualified Thus, 
|  we can have M.Ix( index ), but not M.Ix( T.index ).
| 
| I don't see a compelling reason to outlaw the latter.  We can 
| permit the subordinate name to be unqualified, but why should 
| we enforce it? Ditto for method names in instance decls.

Allowing qualified names on the *lhs* of instance decls involves
two new productions (qfunlhs, etc) that I have only just nuked.  I
sent mail about that some while ago, to see if anyone really thought
we should keep it.

Then, for export lists, the argument becomes one of uniformity 
(with instance decls) and simplicity.   It seems compelling enough to
me.

Thanks for your wording suggestions.

Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



gcd 0 0

2001-12-11 Thread S.D.Mechveliani

People write about the Report definition of
  gcd x y  
as of greatest integer that divides x and y,
and mention
   gcd 0 0 = 0

But 2 also divides 0, because  2*0 = 0.

Does the Report specify that   gcd 0 0   is not defined?

For an occasion: probably, it is better to specify this.

-
Serge Mechveliani
[EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: GCD

2001-12-11 Thread Kent Karlsson


I don't think preorders of any kind should be involved here.
Just the ordinary order on integers. No divisibility preorder (I'm not
sure how that is even defined, so how it could be natural beats me), no
absolute value.

I find the unaltered text Simon quoted to be fine as is.

But for those who like to be more precise (forgive the TeXese):


% Most of you may wish to stop reading at this point.



% I is the set of integers representable in the integral datatype.
% result_I may return overflow or the argument, as appropriate.

\begin{example}\atab
  $gcd_I : I \times I \rightarrow I \cup \{\overflow, \infinitary\}$
\end{example}
\begin{example}\atab
  $gcd_I(x,y)$
\$= result_I(\max\{v \in \ZZ ~~|~~ v|x $ and  $v|y\})$\\
\  \if $x,y \in I$ and ($x \neq 
0$ or  $y \neq 0$)\\
\$= \infinitary(\posinf)$  \if $x = 0$ and $y = 0$
\end{example}

% There is no need to say v0 above, since there are always positive values in that
% set, and max picks the largest/greatest one.  0 has all integer values except(!) 0
% as divisors. So for gcd 0 0 (maximum, supremum really, of the intersection of the two
% sets of divisors) the result is really positive infinity, which should be the result
% returned when representable (recommendable for Haskell's Integer datatype). gcd will
% overflow for instances like gcd (minBound::Int) (minBound::Int). 

\begin{example}\atab\\
  $lcm_I : I \times I \rightarrow I \cup \{\overflow\}$
\end{example}
\begin{example}\atab
  $lcm_I(x,y)$
\$= result_I(\min\{v \in \ZZ ~~|~~ x|v $ and $ y|v $ and $ v  0\})$\\
\  \if $x,y \in I$ and $x \neq 0$ and $y \neq 
0$\\
\$= 0$ \if $x,y \in I$ and ($x = 0$ or  $y = 0$)
\end{example}

% the v0 is needed here, since the set here would otherwise always contain
% infinitely many negative values, and then minimum of that...




Kind regards
/kent k



 -Original Message-
 From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]]On
 Behalf Of S.M.Kahrs
 Sent: den 11 december 2001 11:21
 To: [EMAIL PROTECTED]
 Subject: Re: GCD
 
 
 The natural reading of 'greatest' is, of course,
 the greatest in the divisibility preorder (it's partial order
 on natural numbers but only a preorder on integers).
 Thus, gcd 0 0 = 0.
 
 3 and -3 are equivalent in that preoder.
 
 Thus, an additional comment may be in order.
 
 Stefan
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



gcd 0 0

2001-12-11 Thread George Russell

S.D.Mechveliani wrote
 Does the Report specify that   gcd 0 0   is not defined?
Yes.  The Report definition says
   gcd  :: (Integral a) = a - a - a  
   gcd 0 0  =  error Prelude.gcd: gcd 0 0 is undefined
   gcd x y  =  gcd' (abs x) (abs y) 
   where gcd' x 0  =  x 
 gcd' x y  =  gcd' y (x `rem` y)  

On reflection, this is quite right.  a divides b = there is an
integer n with na = b.  Thus any integer divides 0, and so the
greatest common divisor would have to be the greatest integer,
which is nonsense. 

Of course if you adopt Stephan Kahrs definition of greatest, taken with respect
to the partial order a=b = a divides b, then gcd 0 0 = 0, because 0 is indeed
the greatest integer in this ordering.  Mathematically this makes sense, but it's not 
necessarily
what people expect.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: gcd 0 0

2001-12-11 Thread Alan Bawden

   From: George Russell [EMAIL PROTECTED]
   Date: Tue, 11 Dec 2001 18:18:31 +0100
   ...
   Yes.  The Report definition says
  gcd  :: (Integral a) = a - a - a
  gcd 0 0  =  error Prelude.gcd: gcd 0 0 is undefined
  gcd x y  =  gcd' (abs x) (abs y)
  where gcd' x 0  =  x
gcd' x y  =  gcd' y (x `rem` y)

   On reflection, this is quite right.  a divides b = there is an
   integer n with na = b.  Thus any integer divides 0, and so the
   greatest common divisor would have to be the greatest integer,
   which is nonsense. 

   Of course if you adopt Stephan Kahrs definition of greatest, taken
   with respect to the partial order a=b = a divides b, then gcd 0 0 =
   0, because 0 is indeed the greatest integer in this ordering.
   Mathematically this makes sense, but it's not necessarily what people
   expect.

If you take the point-of-view that gcd is actually an operation on
ideals, then gcd(0, 0) is 0.  I.e. define gcd(x, y) to be the smallest 
z = 0 such that {m*x + n*y | m, n in Z} = {n*z | n in Z}.  This is
probably the most natural and general definition of gcd, and is, in fact,
what many mathematicians would expect.

Also, it is nice to be able to know that gcd(x, 0) = x for -all- x.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Layout rule (again)

2001-12-11 Thread Ian Lynagh


I'm afraid it doesn't seem to be quite right yet  :-(

Consider

instance Foo Maybe where
foo = 5

=

{4}instance Foo Maybe where
{4}foo = 5

=

{instance Foo Maybe where
{}}foo = 5

The second {4} has meant there is no 4 to cause an implicit semicolon
to be inserted. This can be fixed by changing

L ({n}:ts) (m:ms) = { : (L ts (n:m:ms)) if n  m, (Note 1)
  = { : } : (L ts (m:ms)) otherwise

to

L ({n}:ts) (m:ms) = { : (L ts (n:m:ms))   if n  m, (Note 1)
  = { : } : (L (n:ts) (m:ms))   otherwise


Thanks
Ian, having a bad day, predominantly due to the layout rule  :-(


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: haxml

2001-12-11 Thread Jens Petersen

David Smallwood [EMAIL PROTECTED] writes:

 Does anyone know of a mirror site where I can download the latest
 version of HaXml.  (Connection to York is - and has been for a
 while - apparently down:  
ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/HaXml-1.02.tar.gz, that is)

The above url seemed to work for me just now.

Jens

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANN: GHC 5.02.1 RPMs including xlib and HGL packages

2001-12-11 Thread Manuel M. T. Chakravarty

The following might be of special interest to people who are
using Paul Hudak's Haskell textbook for teaching and or
study and would like to run the SOE graphics examples with
GHC - or if you simply want to have an X-based graphics
library for an application.

GHC's source distribution contains the two library packages
`xlib' and `HGL' (Alastair Reid's Haskell Graphics Library)
as part of hslibs, which are not by default built and
installed.  For our local teaching needs at the University
of New South Wales, we have produced a patched version of
GHC 5.02.1 that includes the aforementioned libraries in a
working form.  Haskell modules can be compiled or linked
against these libraries, by providing the command line
options `-package xlib' and `-package HGL', respectively (or
you can specify them using the :s command in the
interpreter).

RPM packages for x86 GNU/Linux based on glibc 2.2 (eg,
RedHat 7.x) containing GHC 5.02.1 including the xlib and HGL
packages are available as

ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-5.02.1-graphics.1.i386.rpm
ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-prof-5.02.1-graphics.1.i386.rpm
ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-doc-5.02.1-graphics.1.i386.rpm

with the source RPM at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/ghc-5.02.1-graphics.1.src.rpm

The source RPM contains a patched source tar ball and build
instructions in the form of an RPM .spec that may be used to
build the packages for other Linux distributions and on
other Unix systems.  (NB: GreenCard need not be installed to
build this package, as a throw-away version of GreenCard is
included in the tar ball - ie, it is used in the build
process, but not installed.)

Cheers,
Manuel

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell