Folks,
Kent Karlsson has asked that we reconsider what integral division
and remainder functions we have in Haskell. To do this right,
I think we need to consider the integral coercion ("rounding")
functions, as well.
To remind everyone of the background on this issue, there is
a basic problem
|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
Simon,
For some reason, I can't find the relevant messages about this,
but my recollection is that during the 1.1 revision (maybe earlier)
the Glaswegians discussed length and friends and recommended
that I do just what was done: making the result of length specifically
Int, but leaving take,
Folks,
There was a small omission in the Integral declaration I just sent;
the first line should be
class (Real a, Ix a) = Integral a where
Similarly, the Real declaration begins
class (Num a, Enum a) = Real a where
This is from Mikael Rittri's proposal.
--Joe
|The new unzip* functions in 1.2 are not suitable for unzipping an
|infinite list. (What Phil called "A splitting headache".)
|Is this deliberate or a mistake? I'd like them to be lazier.
A mistake, thanks. I've fixed it.
--Joe "I hate ^-patterns" Fasel
Folks,
Kent has pointed out to me that the Haskell's use of `div` for truncating,
as opposed to flooring, division is incompatible with both SML and
Miranda, whereas neither Scheme nor Common Lisp have a function by
that name. (Scheme calls it "quotient".) I am willing to change `div`
to
|At the last minute, I have found some Enum bugs in 1.2.beta.
|As I don't know if they have been fixed in 1.2.gamma, which
|I guess was circulated yesterday, here they are:
Thanks, Mikael.
| 1) According to the specification (section 3.9), the
| value of
|
| [ 7, 7 .. 3 ]
|
Let me try that again:
rationalToRealFloat:: (RealFloat a) = Rational - a
rationalToRealFloat x = x'
where x'= f e
f e = if e' == e then y else f e'
where y = encodeFloat (round (x * (b%1)::(-e)) e
(_,e') =
Folks,
Here's an attempt at rationalToRealFloat (formerly known as
rationalToFloating):
rationalToRealFloat:: (RealFloat a) = Rational - a
rationalToRealFloat x = x'
where x'= f e
f e = if e' == e then y else f e'
where y = encodeFloat
| Tonny Davie says
|
| Evan Ireland says
|
| As Nigel and I have
| pointed out to numerous people (including Haskell committee members), the
| statement that stream I/O cannot be efficiently emulated by continuation I/O
i
| true only if the continuation model being used is lacking in certain
| ! It is the responsibility of the programmer to enforce bounds
| ! checking when required in non-derived instances of class @Ix@.
| ! An implementation is not required to check that an index
| ! lies within the bounds of an array when accessing that array.
|
| The above is fine by me, but here
| paul Hudak in his 'gentle introduction to haskell" says that a where clause
| is allowed only at the top level of a set of equations or case expression.
|
| So you cannot declare
| let
| f x = z / y where z = x + y
| in
|
| I do not know the reason why this
| Array notation conventions aside, I think the simple rule that normal
| application has higher precedence than infix application is a Big Win.
| Perhaps the committee should have introduced special syntax for arrays,
| but that was simply not palatable to most of the members, even though
| it
|Given that layout has been used in Miranda, Haskell, etc., to determine
|when one thing ends and another begins, it might be worth trying the
|same idea within expressions. The suggestion is that any subexpression
|that contains no white space but is surrounded by white space has
|implied
|From: "Shah Namrata Abhaykumar" [EMAIL PROTECTED]
|Subject: Haskell I/O
|
|I am trying to understand I/O in haskell. I have trouble understanding
|how it is referentially transperant ?
|Consider that main is,
|
|main resps = [req1,req2,req3,req4]
| where req1 =
|Paul Hudak writes:
|For every bad story there is a good one.
|
|For every bad story there are two good ones. Recently, a local
|hospital suffered many malpractice suits due to faulty software in
|their X-Ray machine. So, they decided to rewrite the code in Haskell
|for more
I know it's late in the day for most of you (or already tomorrow),
but a colleague of mine here at Los Alamos has made a suggestion
I just have to pass along:
Will Partain writes
|We might then match against a list of Foos (type "[Foo]") as follows:
|
|case expr of
| /^{Foo1 _
David Wakeling writes
|Yes, Certainly. Here at York we have a small electrical hoist in one of the
|Departmental stairwells which is used for lifting expensive and delicate
|equipment onto the upper floor of the building. As part of an experiment in
|real time functional programming, I wrote a
| Oh ye Haskell wizards. Is the following program syntactically legal
| or not?
|
| x = leta = let { b=1;
| c=2
| } in 3
| in 4
|
| I.e. is the layout rule from an outer scope in effect even inside
| explicit brackets?
Obviously, this needs clarification.
|Joe writes:
| [My simple syntax for LHSes] doesn't cover things like
|
| (f .* g) x y = f (g x y)
|
|and proposes a syntax which is the same as my simple proposal,
|but covers exactly this also.
|
| lhs ::= (var | @(@ ilhs @)@) apat+
| | ilhs
| | pat
|
| ilhs ::= pat{i+1} varop(n,i)
|Syntax
|~~
|* Left-hand side syntax. PROPOSED DECISION: go with Kevin's suggestion.
|It is simple, does not require modification if we abandon n+k patterns, and
|nobody has objected to it. Kevin has implemented it, and John Peterson
|(our other implementor) agrees. All agree that the
21 matches
Mail list logo