Re: drop take [was: fixing typos in Haskell-98]

2000-01-28 Thread Jan Kort

Marcin 'Qrczak' Kowalczyk wrote:
 My preference is still (B). (A) is not *very* bad, but should really
 replicate (-7) "foo" be []?

Mine too.

Actually after writing my own version of "drop" it turns out that
in my case n  0 is a programmer error and n  length xs a user error.
So what you end up with (if (B) is choosen) is something like:

bafDrop :: Int - String - String
bafDrop i xs | i  length xs = bafError "corrupt BAF file"
 | otherwise = drop i xs

Of course n  0 isn't always a programmer error and you might want
to overwrite it. So that would suggest (A), but right now (B) is my
favourite, because I can't think of a practical example where n  0
would be a user error.

Actually, (A) might be better, the extra check for i  0 is not
time consuming anyway. I guess flipping a coin to choose between
(A) and (B) would work just as well (provided this doesn't lead
to a discussion about what coin to use).

  Jan

P.S. Now that I see the "bafDrop" outside the code, it looks odd. I
 have no right claiming that the BAF -file- is corrupt at that
 point. I'll have to rewrite this using some exception Monad.
 Since this would make the code even bigger I might as well
 put the entire code of drop in it. So much for code reuse...



Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Hamilton Richards

The take-drop law I've always liked is

take n xs ++ drop n xs = xs, for all lists xs and all naturals n.

I agree that (take n _) and (drop n _) should both give errors for n  0.

On the other hand, I don't buy the argument that (take 1 []) should be
undefined because (head []) is undefined. Since head :: [a] - a, (head [])
really has no sensible value, but (take n) :: [a] - [a], so [] is a
reasonable value for (take 1 []).

How about these definitions? They're like the Haskell98 prelude definitions
except that n0 is always an error, even if the list is [].

   take 0 _   = []
   take n _ | n0 = error "Prelude.take: negative argument"
   take n []  = []
   take n (x:xs)  = x : take (n-1) xs

   drop 0 xs  = xs
   drop n _ | n0 = error "Prelude.drop: negative argument"
   drop n []  = []
   drop n (x:xs)  = drop n xs

Or these?

   take n xs
 | n==0  = []
 | n 0  = error "Prelude.take: negative argument"
 | null xs   = []
 | otherwise = x : take (n-1) xs'
 where
 (x:xs') = xs

   drop n xs
 | n==0  = xs
 | n 0  = error "Prelude.drop: negative argument"
 | null xs   = []
 | otherwise = drop (n-1) xs'
 where
 (_:xs') = xs

Regards to all,

--Ham



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--





Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Ch. A. Herrmann

 "Hamilton" == Hamilton Richards [EMAIL PROTECTED] writes:

Hamilton How about these definitions? They're like the Haskell98
Hamilton prelude definitions except that n0 is always an error,
Hamilton even if the list is [].

the problem with an unnecessary restriction is that it complicates
reasoning about the program. 
Instead of

   xs
 = { take/drop-law }
   take (n-m) xs ++ drop (n-m) xs

you have to write, e.g.:

   xs
 = { restricted take/drop-law }
   if nm then undefined else take (n-m) xs ++ drop (n-m) xs
 
The problem is that the "-" operator naturally can appear
if you perform cut and paste operations on lists, but
the natural numbers are not closed under negation.

If using a natural type, people will insist on having a partial
minus operation. How should the compiler check that this operation
is well-defined? If the compiler can't, why have this type at all
if the integers are available?

The advantage of solution (A) is that it makes a single principle
exception for values out of range: an unnatural definition,
but solution (B) makes two: undefinedness for negative values and 
an unnatural definition for values that exceed the size of the list,
i.e., (B) puts more work on the programmer.

In general, the larger a domain of an operation is, the simpler
is the handling. If, i.e., a division by zero produces a value
"div by zero" instead of an error message, 
subsequent operations may deal with it and the entire computation can succeed.

-- 
 Christoph Herrmann
 E-mail:  [EMAIL PROTECTED]
 WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html







Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Marcin 'Qrczak' Kowalczyk

Tue, 25 Jan 2000 14:41:54 -0800, Craig Dickson [EMAIL PROTECTED] pisze:

 And I like having "head []" be an error, because if it returned
 [], then it seems to me that that would have nasty implications
 for pattern-matching.

head [] can't return anything than bottom because anything else has
the wrong type. It has no way of inventing a value of arbitrary type
from nothing.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Marcin 'Qrczak' Kowalczyk

Tue, 25 Jan 2000 15:33:25 -0800, Craig Dickson [EMAIL PROTECTED] pisze:

 If "(x:xs)" does not match [], then the reason for this should be
 that [] has no head to bind to x, nor tail to bind to xs;

No, the reason is simply that [] and (:) are distinct constructors.

E.g. the pattern Nothing does not match Just 5 even though there is
no variable that can't be bound.

Pattern matching must do what the semantics of the language requires.
On the other hand, functions can be defined to do anything that
is expressable.

 "head []", "tail []", and "take 1 []" should also fail.

If take would be spelled "take at most", it would certainly not be
required to fail, right? But the name "take" is simpler and the only
difference between the two is that take is defined on more values
(with the "obvious" meaning), has no runtime penalties, so it suffices.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Marcin 'Qrczak' Kowalczyk

Wed, 26 Jan 2000 16:16:39 +0100 (MET), Ch. A. Herrmann 
[EMAIL PROTECTED] pisze:

 the problem with an unnecessary restriction is that it complicates
 reasoning about the program.
 Instead of
 
xs
  = { take/drop-law }
take (n-m) xs ++ drop (n-m) xs
 
 you have to write, e.g.:
 
xs
  = { restricted take/drop-law }
if nm then undefined else take (n-m) xs ++ drop (n-m) xs

Many properties are broken anyway in presence of negative arguments
to take and drop irrelevantly to what they do in that case (if we want
to keep the current definition for nonnegative arguments of course).

drop n . drop m = drop (n+m)  -- try n = -1, m = 1
take n . drop m = drop m . take (n+m) -- try n = 1, m = -1
-- The second could be valid only when drop (-1) = const [],
-- which does not make sense at all.

My preference is still (B). (A) is not *very* bad, but should really
replicate (-7) "foo" be []?

 If using a natural type, people will insist on having a partial
 minus operation. How should the compiler check that this operation
 is well-defined? If the compiler can't, why have this type at all
 if the integers are available?

This is not a valid argument, because it requires adding the result
of 1/0 to the type of rationals, and it says that you must use complex
numbers instead of reals because reals don't have square root defined
on all arguments... Or I can't see the difference.

I don't say that we need the natural type in Haskell. It is so close
to integers (only half of values is wasted) and it is so common to
convert between the two, that it's not worth the duplication and
confusion. I certainly would not want to have to convert the result
of length from natural to integer when I want to compute a signed
difference between two lengths!

 In general, the larger a domain of an operation is, the simpler
 is the handling. If, i.e., a division by zero produces a value
 "div by zero" instead of an error message, subsequent operations
 may deal with it and the entire computation can succeed.

But the larger a domain of an operation is, the larger class of errors
can pass unnoticed in the first place. Especially when the "natural
definition" does not assign any meaning to particular arguments, e.g.
head [].

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




Re: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Pablo E. Martinez Lopez

 Many properties are broken anyway in presence of negative arguments
 
 drop n . drop m = drop (n+m)  -- try n = -1, m = 1
 take n . drop m = drop m . take (n+m) -- try n = 1, m = -1

But following Simon assumption about collapsing integers to naturals,
you can
have

  collapse n | n0 = 0
  collapse n = n

and then 

  drop n = drop (collapse n)
  take n = take (collapse n)

so

  drop n . drop m = drop (collapse n) . drop (collapse m) 
  = drop (collapse n + collapse m)

  take n . drop m = drop m . take (collapse m + n)

I thought I was sure about undefined for n0, but now I'm not so...
I cannot refute the foldr argument, and the collapse thing fixes any
property you can want.
Fidel.



RE: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Brian Boutel

On Thursday, January 27, 2000 2:08 PM, Frank A. Christoph 
[SMTP:[EMAIL PROTECTED]] wrote:

 My preference is still (B). (A) is not *very* bad, but should really
 replicate (-7) "foo" be []?

I could say: Sure, why not? replicate suffers from the same domain problem
as take/drop.

This was not the point of introducing replicate to the discussion. 
The Prelude says, in a comment,

-- replicate n x is a list of length n with x the value of every element

and then defines replicate in terms of take. 

replicate:: Int - a - [a]
replicate n x=  take n (repeat x)

There is a clear assumption on the part of the Prelude authors that take behaves in a 
particular
way, corresponding to the law 
length (take n xs ) === n
but it doesn't. So even the authors of the Prelude got caught by take's inconsistency.

While I dislike functions with a simple, obvious intended semantics being extended in 
non-obvious, 
non-simple ways, because it creates just this kind of error, I understand that many 
people are less concerned
about it. I can live with any of the proposed definitions, but do suggest that 
incorrect statements are corrected.

So, if negative values are to be allowed in take, the comment re replicate should say, 

-- if n =0 replicate n x is a list of length n with x the value of every element

Or, if negative values are *not* to be allowed in take, then fix the present code so 
that they are
not allowed for any list, including [].

--brian





RE: drop take [was: fixing typos in Haskell-98]

2000-01-26 Thread Frank A. Christoph

Brian Boutel wrote:
 On Thursday, January 27, 2000 2:08 PM, Frank A. Christoph
 [SMTP:[EMAIL PROTECTED]] wrote:

  My preference is still (B). (A) is not *very* bad, but should really
  replicate (-7) "foo" be []?
 
 I could say: Sure, why not? replicate suffers from the same
 domain problem
 as take/drop.

 This was not the point of introducing replicate to the discussion.
 The Prelude says, in a comment,

 -- replicate n x is a list of length n with x the value of every element

 and then defines replicate in terms of take.

 replicate:: Int - a - [a]
 replicate n x=  take n (repeat x)

I don't see that there is any great difference between that and the Prelude
comment describing take:

-- take n, applied to a list xs, returns the prefix of xs of length n, or xs
itself if n  length xs.

Both descriptions are equally undefined w.r.t. negative arguments.

My point is that when the behavior of replicate was described using the
equation above, I think the authors did not intend (although I admit you
would know better than me :) to define replicate in terms of the behavior of
take, whatever it happens to be, but rather in terms of a specific
mathematical function which they wrongly thought take denoted. We all agree
that take is ill-defined; replicate is ill-defined for the exact same
reason, so I would presume that _in principal_ the semantics of replicate
are also up for grabs. So I'm just saying you can't argue for a specific way
of completing take by just pointing at replicate if you want to respect the
spirit (i.e., intended meaning) and not just the letter of the Prelude.

That said, I certainly think we _should_ define the new behavior of
replicate so that it agrees with the above equation, if possible. (In other
words, I was just nitpicking. :) I agree with everything else you wrote:

--fac

 There is a clear assumption on the part of the Prelude authors
 that take behaves in a particular
 way, corresponding to the law
 length (take n xs ) === n
 but it doesn't. So even the authors of the Prelude got caught by
 take's inconsistency.

 While I dislike functions with a simple, obvious intended
 semantics being extended in non-obvious,
 non-simple ways, because it creates just this kind of error, I
 understand that many people are less concerned
 about it. I can live with any of the proposed definitions, but do
 suggest that incorrect statements are corrected.

 So, if negative values are to be allowed in take, the comment re
 replicate should say,

 -- if n =0 replicate n x is a list of length n with x the value
 of every element

 Or, if negative values are *not* to be allowed in take, then fix
 the present code so that they are
 not allowed for any list, including [].

 --brian








RE: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Simon Peyton-Jones

|  Why not do what python does?

Thanks for an interesting suggestion, Alex!

However, we are in typo-fixing mode here.  In the
interests of helping this discussion converge I'm 
going to exercise my dictatorial powers.  Though Alex's
suggestion has its attractions, I judge it too big a change
to apply at this stage in the H98 process.  I think we
should adopt one of the three alternatives I proposed.
No one has supported C, so we are down to:

(A) Make them defined for any n.  If n  0, do something reasonable:
take:   give empty list
drop:   give whole list

(B) Make them defined for n  length xs, but fail for n  0.


I've heard suppport for both.  Personally I 
favour (A) but only mildly.  (B) is a smaller change.

Simon



Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Tommy Thorn

Chris Okasaki wrote:

 For the people that share this sentiment, can you please
 explain why ints that are too big should not similarly
 give an error?  I can see both being ok, or both being
 errors.  I just don't see why one should be ok and the
 other an error.

IMHO, both should be errors.  If we really need, we can provide
takeSloppy, takeBackwards, etc, but the default should be a tight as
possible to catch errors.

I still believe that take and drop should satisfy the compositional laws
on legal arguments.

Regards,

  Tommy





Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread D. Tweed

On Tue, 25 Jan 2000, Chris Okasaki wrote:

  I'm with the option (B): negatives are just outside 
  the domain of takedrop, and should give you an error 
  message.
 
 For the people that share this sentiment, can you please
 explain why ints that are too big should not similarly
 give an error?  I can see both being ok, or both being
 errors.  I just don't see why one should be ok and the
 other an error.

As a purely _pragmatic_ argument: code that does things by taking blocks
of stuff from a list (e.g., some form of block based compression
technique) could be written (in broad outline)

f [] = []
f a xs =res:f a' zs
(ys,zs)=splitAt 40 xs
(a',res)=doStuff a xs

If the list isn't a multiple of 40 then only doStuff needs to know how to
deal with incomplete blocks with B; with values too big being an error f
has to check at each point whether there's enough list there before trying
the splitAt. So you have a way of ascertaining that length  40 without
diverging on infinite lists. It all gets complicated, and this pattern
of `eat fixed size chunks while the list isn't depleted' seems common
enough to warrant simple programming.

I can't think of a pattern of usage that's natural that
leads to wanting to take negative portions of the list, but maybe that's
my imagination...

___cheers,_dave
www.cs.bris.ac.uk/~tweed/pi.htm Farenheit 451 is the temperature at  
email: [EMAIL PROTECTED] which paper burns. Let's do an experiment to
work tel: (0117) 954-5253 see what temperature melts human brain cells.




Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread D. Tweed

On Tue, 25 Jan 2000, D. Tweed wrote:

Oops, fixing two thinko's

 f _ [] = []
 f a xs =res:f a' zs
 (ys,zs)=splitAt 40 xs
 (a',res)=doStuff a ys

(My haskell coding is getting worse than my C++, which I didn't believe
possible...)

___cheers,_dave
www.cs.bris.ac.uk/~tweed/pi.htm Farenheit 451 is the temperature at  
email: [EMAIL PROTECTED] which paper burns. Let's do an experiment to
work tel: (0117) 954-5253 see what temperature melts human brain cells.





Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Joe Fasel

Phil Wadler writes:
| I'm with Jon Fairbairn on this.  Negative arguments are an error
| because the domain of take and drop is the naturals.  The problem
| is that we use Int to represent naturals.  -- P
| 
|  For the people that share this sentiment, can you please
|  explain why ints that are too big should not similarly
|  give an error?  I can see both being ok, or both being
|  errors.  I just don't see why one should be ok and the
|  other an error.

I'm with Phil and Jon on this.  The "natural" domain for take
and friends is the naturals.  The question of whether negative arguments
are an error or are equivalent to zero may be slightly tricky, though:
If we did have the naturals as a type, how would we define the
predecessor function on zero?  It's either zero or undefined.  Negative
arguments to take should go the same way.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545




Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Chris Okasaki

 I'm with Jon Fairbairn on this.  Negative arguments are an error
 because the domain of take and drop is the naturals.  The problem
 is that we use Int to represent naturals.  -- P

Yep, this is exactly the same argument we had about this
a year or two ago, Phil.  My attitude about the "implicit Nat"
argument is the same as it was then -- if you want the functions
to be over Nat's then *say* Nat in the type, not Int.  This
could be done in at least two relatively lightweight ways.

  -- provide a Nat type that maps to unsigned integers
  -- provide a simple type synonym
 type Nat = Int
 along with a prominent comment that any function that
 *says* Nat in its type should raise an error on a negative argument

I would have no arguments with either approach, or with any other
approach that makes Nat explicit in the type.

But if the type *says* Int, then it should have reasonable behavior
for ints.  I look at the negative case as being equivalent to
standard mathematical treatment of ranges such as i..j, where the
range is considered to be empty if j  i.  Allowing take/drop to
handle negative arguments should be useful to exactly the same
extent as that mathematical convention.

Chris






Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Philip Wadler

Chris,  I admit your argument about symmetry is attractive.
If you could put forward a concrete application, on a par with
the `break into blocks' application given earlier, you would
likely sway me.  -- P




Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Joe Fasel

Chris Okasaki writes:
| But if the type *says* Int, then it should have reasonable behavior
| for ints.  I look at the negative case as being equivalent to
| standard mathematical treatment of ranges such as i..j, where the
| range is considered to be empty if j  i.  Allowing take/drop to
| handle negative arguments should be useful to exactly the same
| extent as that mathematical convention.

I find this persuasive.  That suggests these definitions:

 take _ [] = []
 take n _ | n = 0 = []
 take (n+1) (x:xs) = x : take n xs

 drop _ [] = []
 drop n xs | n = 0 = xs
 drop (n+1) (_:xs) = drop n xs

 splitAt n xs = (take n xs, drop n xs)

The call some have made for the tightest possible error
checking also has merit, however.  That would suggest
these definitions:

 takeExactly 0 _ = []
 takeExactly (n+1) (x:xs) = x : takeExactly n xs
 takeExactly _ _ = undefined

 dropExactly 0 xs = xs
 dropExactly (n+1) (_:xs) = dropExactly n xs
 dropExactly _ _ = undefined

 splitAtExactly n xs = (takeExactly n xs, dropExactly n xs)

I would say that the more loosely-defined functions definitely
belong in the library and that it is a matter of taste whether
or not to include the tighter ones.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email:  [EMAIL PROTECTED]
Technology Modeling and Analysisphone:  +1 505 667 7158
University of Californiafax:+1 505 667 2960
Los Alamos National Laboratory  postal: TSA-7 MS F609
Los Alamos, NM  87545





Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Marcin 'Qrczak' Kowalczyk

Tue, 25 Jan 2000 12:14:29 -0500 (EST), Chris Okasaki [EMAIL PROTECTED] pisze:

 I would have no arguments with either approach, or with any other
 approach that makes Nat explicit in the type.
 
 But if the type *says* Int, then it should have reasonable behavior
 for ints.

I can't agree with that argument. What is a difference between "if the
type says [a], then it should have reasonable behavior for all lists"?
If it's in the definition of reasonable behavior, why tail [] being
undefined is reasonable where take (-1) [] is not?

It's good when a function is total, but types don't always allow to
nicely ensure this.



Another similar case: cycle []. AFAIK it used to be [], but now it
is undefined. I don't have a strong opinion on either side, although
undefined looks a bit more natural: "cycle x = x ++ cycle x" without
exceptions. One could easily test for empty argument in constant
time anyway.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




RE: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Brian Boutel

On Wednesday, January 26, 2000 9:12 AM, Joe Fasel [SMTP:[EMAIL PROTECTED]] wrote:
 
 
 The call some have made for the tightest possible error
 checking also has merit, however.  That would suggest
 these definitions:
 
  takeExactly 0 _ = []
  takeExactly (n+1) (x:xs) = x : takeExactly n xs
  takeExactly _ _ = undefined
 
  dropExactly 0 xs = xs
  dropExactly (n+1) (_:xs) = dropExactly n xs
  dropExactly _ _ = undefined
 
  splitAtExactly n xs = (takeExactly n xs, dropExactly n xs)
 
 I would say that the more loosely-defined functions definitely
 belong in the library and that it is a matter of taste whether
 or not to include the tighter ones.

We have seen various proposals about what laws should hold wrt
take and drop. I think there is a reasonable presumption that the 
following  very simple laws should hold first:

length (take n xs) === n
length (drop n xs) === length xs -n

This supports Joe's takeExactly/dropExactly definitions.

--brian




Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Tom Pledger

Hi.

For H98, I prefer option (A).  Option (B) gives an arbitrary
dissimilarity with rangeSize and enumFromTo.  They currently match the
standard mathematical treatment of ranges such as i..j, which Chris
Okasaki mentioned.  I'm not saying that they're sacred, just that a
shift to the style of option (B) is too far-reaching for H98.

For any version of Haskell, I prefer that take n x and drop n x (when
length x  n) should not immediately raise errors, in general.  That
would be too strict.  It's arguable whether errors should be raised in
the special case that x == [].  How similar should drop 1 be to tail?

Regards,
Tom



Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Craig Dickson

Brian Boutel [EMAIL PROTECTED] wrote:

 We have seen various proposals about what laws should hold wrt
 take and drop. I think there is a reasonable presumption that the
 following  very simple laws should hold first:

 length (take n xs) === n
 length (drop n xs) === length xs -n

Does that not imply that "take n xs" when n  (length xs) should be an
error? I would support that for Haskell 2000, but not for Haskell 98; it's
too big a change, and goes far beyond the original goal of resolving the
problem of "take n xs | n  0".

For Haskell 98, I still favor the proposal:

take n xs | n  0 = []
drop n xs | n  0 = xs

For Haskell 2000, I feel that the list functions should be consistent in
their treatment of empty lists. If "head []" is an error, then "take 2 [1]"
should also be an error. And I like having "head []" be an error, because if
it returned [], then it seems to me that that would have nasty implications
for pattern-matching. I don't want a pattern like "(x:xs)" to match the
empty list, which it presumably would if "head []" and "tail []" did not
fail (x and xs would both be bound to []).

So, if "head []" and "tail []" are going to fail, then other things that
imply looking at the head or tail of [] should also fail, including "take 2
[1]" and "drop 2 [1]".

Craig





Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Craig Dickson

Tom Pledger [EMAIL PROTECTED] wrote:

 Craig Dickson writes:
   [...]
   I don't want a pattern like "(x:xs)" to match the empty list, which
   it presumably would if "head []" and "tail []" did not fail (x and
   xs would both be bound to []).

 I don't think it would.  Patterns involve data constructors like []
 and (:), but not functions like head and tail, which may happen to
 obey all sorts of rules, but aren't part of the data type definition.

True, but I think the standard functions, especially those in the prelude,
ought to make sense in terms of the data type's definition, for the sake of
presenting a consistent view of that data type to the programmer. If
"(x:xs)" does not match [], then the reason for this should be that [] has
no head to bind to x, nor tail to bind to xs; and if this is so, then "head
[]", "tail []", and "take 1 []" should also fail. Conversely, if "head []"
and "tail []" succeed, then "(x:xs)" should match the empty list. If this
consistency is not maintained, then the language and its core functions are
presenting a confusing and somewhat contradictory view of what a list is and
how you interact with it.

Craig





Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Matt Harden

Chris Okasaki wrote:
 
  I'm with the option (B): negatives are just outside
  the domain of takedrop, and should give you an error
  message.
 
 For the people that share this sentiment, can you please
 explain why ints that are too big should not similarly
 give an error?  I can see both being ok, or both being
 errors.  I just don't see why one should be ok and the
 other an error.

How about a practical reason: if take has to check the length, it has to
scan the whole list to determine whether to return an error.  This is
more strict (and more complex) than it should be.  For example, if we
define take like this:

   take n _ | n0 = error "take: negative argument"
   take n (x:xs) = x:(take (n-1) xs)
   take 0 _ = []
   take _ [] = error "take: list not long enough"

Then the error when n(length l) is buried at the "end" of the list
returned by take.  OTOH, a drop defined similarly would give an error
immediately if n(length l).  I don't like that asymmetry, do you?  But
I definitely don't think negative values make sense for take  drop,
just as they are an error for (!!).  I think we should be able to define
(!!) as 
 l !! n = head (drop n l)
...without worrying about what drop will do for negative arguments.  A
negative index on a list should uniformly be an error.  I just consider
take to mean "take at most" and drop to mean "drop at most".

I like:
 take 3 (take 50 [1,2,3,4]) == [1,2,3]

By the way, replicate is defined in terms of take in the prelude, so
what do you think (replicate -1 x) should do?

Matt



Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Fergus Henderson

On 25-Jan-2000, Craig Dickson [EMAIL PROTECTED] wrote:
 Brian Boutel [EMAIL PROTECTED] wrote:
 
  We have seen various proposals about what laws should hold wrt
  take and drop. I think there is a reasonable presumption that the
  following  very simple laws should hold first:
 
  length (take n xs) === n
  length (drop n xs) === length xs -n
 
 Does that not imply that "take n xs" when n  (length xs) should be an
 error? I would support that for Haskell 2000, but not for Haskell 98; it's
 too big a change, and goes far beyond the original goal of resolving the
 problem of "take n xs | n  0".

I agree that it is too big a change for Haskell 98.
But I think it would be too big a change for Haskell 2000 too.
Making a change like that could cause previously working programs
to fail, with no warning at compile time, and with the bug showing
up only on certain inputs.  The cost of that would far outweigh
the benefit (which, in the light of the mixed opinions here, seems
dubious anyway).  Making non-backwards-compatible changes to the
semantics of basic prelude functions like take and drop would be
a really bad idea, IMHO.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.



Re: drop take [was: fixing typos in Haskell-98]

2000-01-25 Thread Fergus Henderson

On 26-Jan-2000, Brian Boutel [EMAIL PROTECTED] wrote:
 On Wednesday, January 26, 2000 1:52 PM, Fergus Henderson 
 [SMTP:[EMAIL PROTECTED]] wrote:
 
  I agree that it is too big a change for Haskell 98.
  But I think it would be too big a change for Haskell 2000 too.
  Making a change like that could cause previously working programs
  to fail, with no warning at compile time, and with the bug showing
  up only on certain inputs.  The cost of that would far outweigh
  the benefit (which, in the light of the mixed opinions here, seems
  dubious anyway).  Making non-backwards-compatible changes to the
  semantics of basic prelude functions like take and drop would be
  a really bad idea, IMHO.
 
 Sometimes things are just wrong, and they have to be fixed, however painful 
 that is.
 I would rather have a definition that makes sense, than one that has always 
 been wrong.
 
 This case is not grossly wrong, but it is annoying. Taking and dropping 
 negative numbers of values
 does not make sense.

Sorry, I was probably not making myself clear.
In the discussion above, I was talking about making `take n l'
and `drop n l' report errors if n  length l.
That case is probably used quite widely by existing code,
and so I think changing it now would be a bad idea.

In contrast, I think the `take -1 []' case is the kind of thing
that is likely to be used only extremely rarely, if at all,
in existing code.  I would be happy to change that case to
be an error in H98.

 At the very least we have an inconsistancy in the treatment of negative 
 arguments, which should be fixed.

Agreed.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.



drop take [was: fixing typos in Haskell-98]

2000-01-24 Thread Tommy Thorn

S. Alexander Jacobson writes:
  The correct definitions would be:
  
  take -2 -- drops the last 2 elements from the list
   (takes everything except the last 2 elements)
  drop -2 -- grabs the last 2 elements from the list
   (drops everything except the last 2 elements)

  These are also sane definitions..  

IMHO, that would be the _insane_ definitions :-)  Firstly, nothing
suggests to me that rationale of such behaviour.  Secondly, it would
mean loosing an important set of laws:

  drop n . drop m === drop (n + m)
  take n . take m === take (n + m)

(which, I note in passing, is broken also by suggestion A)

Regards,

   Tommy



Re: drop take [was: fixing typos in Haskell-98]

2000-01-24 Thread Jan Skibinski



 All the proposals break this law as well, so I this argument is weak (if
 not insane :-))
 
 -Alex-

IMHO, a consistency is the most important rule here.

I do not have any problems with any of those proposals,
providing that I can apply similar reasoning to other
functions as well. I do not wish to be forced to remember
that "drop" and "take" are somehow special in treatment
of (illegal/legal?) negative arguments.


Jan








RE: drop take [was: fixing typos in Haskell-98]

2000-01-24 Thread BYRNE, Peter

I'm new to Haskell, but

(1) With regard to the second "law", 
(take 1 . take 5) [1..] 
 does not appear to me to be the same as 
take 6 [1..]

(2) If take and drop are to be defined for negative integers, what happens
to
take (-n) xs
 when n  len xs?  Judging from the definitions proposed:
take (-5) [1..4] == [1,2,3]
 and things look less useful than confusing.

PCB

 -Original Message-
 From: S. Alexander Jacobson [SMTP:[EMAIL PROTECTED]]
 Sent: Tuesday, January 25, 2000 10:16 AM
 To:   Tommy Thorn
 Cc:   [EMAIL PROTECTED]
 Subject:  Re: drop  take [was: fixing typos in Haskell-98]
 
  IMHO, that would be the _insane_ definitions :-)  Firstly, nothing
  suggests to me that rationale of such behaviour.  
 
 The rationale is:
 1. these are useful functions
 2. if this is insane, so is python. The corresponding python is:
 
   def take list n: return list[:n]
   def drop list n: return list[n:]
   
   Python interpreter example:
list="abcdef"
list[:-2]
   'abcd'
list[-2:]
   'ef'
   
   
 3. think of n as being calculated 'mod' length of the list
   take n list | n0 = take (n `mod` (length list)) list
   drop n list | n0 = drop (n `mod` (length list)) list
   --(equivalent definitions)
 
  Secondly, it would mean loosing an important set of laws:
 
drop n . drop m === drop (n + m)
take n . take m === take (n + m)
  (which, I note in passing, is broken also by suggestion A)
 
 All the proposals break this law as well, so I this argument is weak (if
 not insane :-))
 
 -Alex-
 ___
 S. Alexander Jacobson Shop.Com
 1-212-697-0184 voice  The Easiest Way To Shop
 
 
 On Mon, 24 Jan 2000, Tommy Thorn wrote:
 
  S. Alexander Jacobson writes:
The correct definitions would be:

take -2 -- drops the last 2 elements from the list
 (takes everything except the last 2 elements)
drop -2 -- grabs the last 2 elements from the list
 (drops everything except the last 2 elements)
  
These are also sane definitions..  
  
  
  
  Regards,
  
 Tommy
  
 
 
 
 



Re: drop take [was: fixing typos in Haskell-98]

2000-01-24 Thread Dr. Mark E. Hall

"S. Alexander Jacobson" wrote:
 The python behavior is:
 take n list | length list + n  0 = []
 drop n list | length list + n  0 = list
 
 I think this is the correct complement (dual?) of:
 take n list | length list - n  0 = list
 drop n list | lenght list - n  0 = []
 (the current behavior)

Yes, the python behavior above is the correct dual of the current behavior
of "take n" and "drop n" for n = length list. And yes, your proposal for
the case n  0 is consistent and sane as well (calling it insane is too
strong of a judgment for me). However, I do not think it is the *best*
choice among the sane and consistent proposals being offered. I would have
to agree with Fergus Henderson that it would be a very rare situation in
which you need to use "drop n xs" without knowing the sign of "n" ahead of
time *and* your proposed behavior for n  0 is the desired one; and that
if you need a function that takes or drops from the end of a list then you
are surely better off to define a separate function to perform this operation,
not the least because having a different name makes it clear that its purpose
is different from that of the usual "take" or "drop".

Also, it is not accurate to say that your proposal simply amounts to con-
sidering "n" modulo "length xs" when n  0. In fact this is only true for
length xs  n  0. Your own example

 -3  -2  -1  0   1   2   3  
 take""  "a" "ab""abc"   "a" "ab""abc"
 drop"abc"   "bc""c" ""  "bc""c" ""

shows this clearly: take -3 "abc" /= take 0 "abc" and drop -3 "abc" /=
drop 0 "abc", even though -3 is congruent to 0 modulo the length of "abc".

My vote is for behavior (B): have "take n" and "drop n" fail if n  0 in
all cases. I vote for this case because, as several others have already
pointed out, a negative value for "n" is most likely the result of a bug
that should be brought to someone's attention. And you can always define
functions "silent_take" and "silent_drop" that do not complain when
given a negative first argument if you need them. However, if behavior (A)
wins out, I won't complain very much. It's certainly a good second choice,
and one can even argue that mathematically it is the choice most consistent
with the current behavior for n = 0 (this message is already getting long,
so I won't give the argument unless someone asks me to 8-) ).

As for "partition" and "splitAt", I agree with Simon's original proposals
(I am assuming that these are simply the official definitions of the
functions' behaviors, and that implementors are free to use other, more
efficient implementations that have exactly the same behavior, including
strictness behavior).

Mark



  Mark E. Hall
  Mahanakorn University of Technology
  Vanit Building 2, 8th Floor
   1126/1 New Petchburi Road
Bangkok 10400, Thailand
66-2-6553181--7
[EMAIL PROTECTED]
  http://www.mut.ac.th/~mehall