1.2 alpha mistake

1992-02-17 Thread Lennart Augustsson

In the table of Prelude operators (p. 53) the operator :% is
listed, this operator is not (and should not be) exported
from the Prelude, and should be removed from the table.

-- Lennart





Haskell library

1992-02-17 Thread Lennart Augustsson

The Haskell library seems to be contain few entries
(none to be exact), so I've decided to add something.

On animal.cs.chalmers.se I've placed two very simple,
but useful modules.  One implements a random number
generator (a very good one; I didn't design it), and
the other a sorting function that is reasonably efficient.

Share and enjoy!

-- Lennart





Re: Haskell library

1992-02-17 Thread Will Partain

Lennart Augustsson writes:

The Haskell library seems to be contain few entries
(none to be exact), so I've decided to add something.
...

Actually, I've put the Haskell-y bits from Stephen Bevan's archive
into the library here at Glasgow
(ftp.dcs.glasgow.ac.uk:^ftp/pub/haskell/library).  I'll copy Lennart's
bits over sometime soon.  There's a .../library/incoming directory for
anyone wanting to drop something in.

By some magical process, the sites at Yale, Chalmers, and Glasgow will
all end up with the same library bits (eventually).

Will




Report bug

1992-02-17 Thread Lennart Augustsson

The 1.2 preface says that type synonyms are exported with "T..",
shouldn't that be "T(..)"?

-- Lennart





Re: Division, remainder, and rounding functions

1992-02-17 Thread Lennart Augustsson


I think the suggestion Joe has made about division is good,
but I also think it is overkill!

Let's not add even more things to the Prelude that are not
going to be used.  My opinions on this matter is:
- have something which is efficiently implementable
  (i.e. close to what the hardware provides) as the
  primitive, which is what `div` is.
- just add an extra function for what Kent wants, e.g.
infix 7 `quo`
x `quo` y = if x < 0 then x `div` y - 1 elsse x `div` y
  or whatever is approproate.

 -- Lennart







Division, remainder, and rounding functions

1992-02-17 Thread smk

Joe,

Your definition of divFloorRem (and probably divCeilingRem as well)
doesn't seem to be quite right, because I end up with
(-4) `mod` (-3) == -4
because divTruncateRem (-4) (-3) is (1,-1).

The condition in the "if" should be something like
signum r == -signum d
rather than r<0. (Something like this is in the definition of
`mod` on page 89 in 1.2beta.)

Stefan Kahrs






Re: Division, remainder, and rounding functions

1992-02-17 Thread Kent Karlsson


Thanks Joe!  I still don't know why anyone would want
the 'divTruncateRem' function and its derivatives, but ok,
leave them there.  Why not add division with "rounding"
AWAY from zero as well. :-)

/kent k

(I've sent some detail comments directly to Joe.)




Re: Division, remainder, and rounding functions

1992-02-17 Thread jhf

|Your definition of divFloorRem (and probably divCeilingRem as well)
|doesn't seem to be quite right, because I end up with
|   (-4) `mod` (-3) == -4
|because divTruncateRem (-4) (-3) is (1,-1).
|
|The condition in the "if" should be something like
|   signum r == -signum d
|rather than r<0. (Something like this is in the definition of
|`mod` on page 89 in 1.2beta.)
|
|Stefan Kahrs

Right, thanks.  I've committed the error of forgetting that the
divisor can be negative.  I did the rounding methods first, where
the "divisor" is 1, and then did the division methods by (incorrect!)
analogy.  You'd think that after n years of struggling with with
definitions like these, I'd be able to get them right!

So, as you say, this can be fixed thus:

divFloorRem n d =  if signum r == - signum d then (q-1, r+d) else qr
   where qr@(q,r) = divTruncateRem n d

divCeilingRem n d   =  if signum r ==   signum d then (q+1, r-d) else qr
   where qr@(q,r) = divTruncateRem n d

Another way:

divFloorRem n d =  if r < 0 then (q-1, r+d) else qr
   where
   qr@(q,r) = divTruncateRem n' d'
   (n', d') = if d < 0 then ((-n),(-d)) else (n,d)

divCeilingRem n d   =  if r > 0 then (q+1, r-d) else qr
   where
   qr@(q,r) = divTruncateRem n' d'
   (n', d') = if d < 0 then ((-n),(-d)) else (n,d)


--Joe




Re: Modules again

1992-02-17 Thread Simon L Peyton Jones


| Well, here's another problem I've encountered.  Consider this module:
|
|   module M(T) where
|   data T = T
|
| Is this legal?  Clearly I am just trying to export the type T, but it happens
| that the type has a constructor with the same name.  Naming a constructor
| in the export list is explicitely forbidden.  How can the compiler tell
| if I intended naming the constructor or type in the export list?

This one is easy (I think) (for a change).  The module above is quite legal,
and exports the type T but not the constructor.  If you wanted the
constructor to go too, you can write

module M( T(..) )

or

module M( T(T) )

Simon




Modules again

1992-02-17 Thread Lennart Augustsson


Well, here's another problem I've encountered.  Consider this module:

module M(T) where
data T = T

Is this legal?  Clearly I am just trying to export the type T, but it happens
that the type has a constructor with the same name.  Naming a constructor
in the export list is explicitely forbidden.  How can the compiler tell
if I intended naming the constructor or type in the export list?

So, what do you (especially Simon) say, legal or not?

-- Lennart