Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Roman Beslik

 On 29.06.10 08:37, Ketil Malde wrote:

Albert Y.C.Lai  writes:

The doc of deleteBy states: "The deleteBy function behaves like delete, but
takes a user-supplied equality predicate." A precondition is that the
user-supplied predicate is an equality predicate. (>=) is not an equality
predicate, be it in the layperson sense of "it isn't analogous to (==)" or the
mathematical sense of "it isn't an equivalence relation".


One could argue that this is a bad specification.  The type is

   deleteBy :: (a ->  a ->  Bool) ->  a ->  [a] ->  [a]

but there are further limitations on the arguments, and worse, the function
doesn't check this and produce an error if the arguments don't conform,
but just silently produces a meaningless result.
How can 'deleteBy' check that an argument is an equivalence relation? 
(Putting aside that this harms performance.)


--
Best regards,
  Roman Beslik.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ivan Lazar Miljenovic
Daniel Fischer  writes:

> On Tuesday 29 June 2010 13:02:20, Ivan Lazar Miljenovic wrote:
>>
>> That's like asking why we have mapM and forM, etc.
>
> Yes, why?
>
> (okay, I use forM too, it's so much more readable with a short list and a 
> long action)

Exactly; using "deleteBy p" (if it was fixed in this sense) would be less
ambiguous in what it's there for and less repetitive than using "filter
(not p)" all the time.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Daniel Fischer
On Tuesday 29 June 2010 13:02:20, Ivan Lazar Miljenovic wrote:
>
> That's like asking why we have mapM and forM, etc.

Yes, why?

(okay, I use forM too, it's so much more readable with a short list and a 
long action)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Daniel Fischer
On Tuesday 29 June 2010 12:50:34, Ketil Malde wrote:
> Daniel Fischer  writes:
> >> An important point of a powerful type system is to model your program
> >> so that only sensible code is legal.
> >
> > That would be an awesomely powerful type system :)
>
> Heh.  But while we're waiting for it, we can try to use what we got to
> eliminate as much non-sensical code as possible.

+1


>
> ...which is a worry my implementation removed by letting the user decide
> through partial application.
>

Aye.

> > For a symmetric relation, you needn't care.
>
> But the docs (are interpreted to) say equivalence relation, so woe
> betide you if you give it a symmetric but non-transitive or
> non-reflexive function!
>
>deleteBy (\x y -> abs (x-y) == 2) 5 [1..5]

grin

>
> Anyway: I guess the point here is that if all 'deleteBy f x ys' does
> with arguments f and x is apply f to x and then use the result, we might
> as well feed it that result and eliminate a lot of uncertainity as well
> as some documentation all too few of us bother to read.
>

Full agreement!

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ivan Lazar Miljenovic
Daniel Fischer  writes:

> That's more common, yes (I don't remember ever having used delete(By) 
> intentionally). But we've filter for that, so it wouldn't make sense to 
> give delete(By) the same semantics. Hence, if you provide both names, what 
> else could deleteBy do?

That's like asking why we have mapM and forM, etc.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Daniel Fischer
On Tuesday 29 June 2010 12:46:21, Ivan Lazar Miljenovic wrote:
>
> At most one element, yes; I question why that design decision was made
> as I'm more likely to want to delete all values rather than just the
> first one

That's more common, yes (I don't remember ever having used delete(By) 
intentionally). But we've filter for that, so it wouldn't make sense to 
give delete(By) the same semantics. Hence, if you provide both names, what 
else could deleteBy do?

> (does anyone actually like/rely on the current functionality
> of delete/deleteBy w.r.t. repeated values?).

I doubt it.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ketil Malde
Daniel Fischer  writes:

>> An important point of a powerful type system is to model your program so
>> that only sensible code is legal.

> That would be an awesomely powerful type system :)

Heh.  But while we're waiting for it, we can try to use what we got to
eliminate as much non-sensical code as possible.

(Which, btw, I think is an under-sold point: people used to C-style type
systems think that all the type system does is label variables for you,
which dynamic type systems (like our algebraic data types) let you do
the same run-time.  But you get a lot more mileage by careful type
design.)

>> I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]'
>> would do.
>
> Well, if you don't know about filter, you could think it deletes all 
> elements satisfying the predicate, but apart from that, it's clear.

I'd probably call it 'filter1', but that's just my personal convention. 

>> And I just don't see what the requirement for an equivalence
>> relation buys you.

> For the type deleteBy has, predictability. Currently, you can't know 
> whether deleteBy pred x tests pred x y or pred y x without looking at the 
> source. 

...which is a worry my implementation removed by letting the user decide
through partial application.

> For a symmetric relation, you needn't care.

But the docs (are interpreted to) say equivalence relation, so woe
betide you if you give it a symmetric but non-transitive or
non-reflexive function!

   deleteBy (\x y -> abs (x-y) == 2) 5 [1..5]

Anyway: I guess the point here is that if all 'deleteBy f x ys' does
with arguments f and x is apply f to x and then use the result, we might
as well feed it that result and eliminate a lot of uncertainity as well
as some documentation all too few of us bother to read.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ivan Lazar Miljenovic
Ketil Malde  writes:

> Max Rabkin  writes:
>
>> Your deleteBy is (filter . not), isn't it?
>
> With the caveat that I haven't actually used it, my impression is that
> delete only removes one element, while filter removes all of them.

At most one element, yes; I question why that design decision was made
as I'm more likely to want to delete all values rather than just the
first one (does anyone actually like/rely on the current functionality
of delete/deleteBy w.r.t. repeated values?).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ketil Malde
Max Rabkin  writes:

> Your deleteBy is (filter . not), isn't it?

With the caveat that I haven't actually used it, my impression is that
delete only removes one element, while filter removes all of them.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ivan Lazar Miljenovic
Max Rabkin  writes:

> On Tue, Jun 29, 2010 at 11:46 AM, Ketil Malde  wrote:
>>  deleteBy :: (a -> Bool) -> [a] -> [a]
>>
>> I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]'
>> would do. And I just don't see what the requirement for an equivalence
>> relation buys you.
>
> Your deleteBy is (filter . not), isn't it?

"filter . (not .)" actually.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Daniel Fischer
On Tuesday 29 June 2010 11:46:47, Ketil Malde wrote:
>
> An important point of a powerful type system is to model your program so
> that only sensible code is legal.

That would be an awesomely powerful type system :)

> This makes me wonder why deleteBy is
> defined so loosely, instead of e.g.
>
>   deleteBy :: (a -> Bool) -> [a] -> [a]

That would've been the (a) safer choice.

>
> I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]'
> would do.

Well, if you don't know about filter, you could think it deletes all 
elements satisfying the predicate, but apart from that, it's clear.

> And I just don't see what the requirement for an equivalence
> relation buys you.

For the type deleteBy has, predictability. Currently, you can't know 
whether deleteBy pred x tests pred x y or pred y x without looking at the 
source. For a symmetric relation, you needn't care.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Max Rabkin
On Tue, Jun 29, 2010 at 11:46 AM, Ketil Malde  wrote:
>  deleteBy :: (a -> Bool) -> [a] -> [a]
>
> I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]'
> would do. And I just don't see what the requirement for an equivalence
> relation buys you.

Your deleteBy is (filter . not), isn't it?

--Max
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Ketil Malde
Daniel Fischer  writes:

>> Maybe it is because deleteBy is defined wrongly? i.e. it is not logical,
>> doesn't follow the common sense user might expect. It accepts any
>> predicate but narrows requirements only in docs.

> Unfortunately, you can't easily encode the requirement that it ought to be 
> an equivalence relation via types. 

This is just another way of saying the same thing :-)

An important point of a powerful type system is to model your program so
that only sensible code is legal.  This makes me wonder why deleteBy is
defined so loosely, instead of e.g.

  deleteBy :: (a -> Bool) -> [a] -> [a]

I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]'
would do. And I just don't see what the requirement for an equivalence
relation buys you.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Daniel Fischer
On Tuesday 29 June 2010 10:47:40, Zura_ wrote:
> Maybe it is because deleteBy is defined wrongly? i.e. it is not logical,
> doesn't follow the common sense user might expect. It accepts any
> predicate but narrows requirements only in docs.

Unfortunately, you can't easily encode the requirement that it ought to be 
an equivalence relation via types. So putting it in the docs and hoping 
nobody gets burned too badly is probably the best one can do.

>
> Maybe best could be to just take a value for comparison and use "=="
> against it?

That's the plain delete.

> ("overloaded" or "built-in" (I'm a C++ engineer but as I
> know it is possible in Haskell as well.))
>
> And to have separate delete which accepts arbitrary predicate. (As it is
> now.)
>
> Regards,
> Zura
>
> Albert Y. C. Lai wrote:
> > The doc of deleteBy states: "The deleteBy function behaves like
> > delete, but
> > takes a user-supplied equality predicate." A precondition is that the
> > user-supplied predicate is an equality predicate. (>=) is not an
> > equality predicate, be it in the layperson sense of "it isn't
> > analogous to (==)" or the
> > mathematical sense of "it isn't an equivalence relation".

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Zura_

Maybe it is because deleteBy is defined wrongly? i.e. it is not logical,
doesn't follow the common sense user might expect. It accepts any predicate
but narrows requirements only in docs.

Maybe best could be to just take a value for comparison and use "==" against
it? ("overloaded" or "built-in" (I'm a C++ engineer but as I know it is
possible in Haskell as well.))

And to have separate delete which accepts arbitrary predicate. (As it is
now.)

Regards,
Zura


Albert Y. C. Lai wrote:
> 
> The doc of deleteBy states: "The deleteBy function behaves like delete,
> but
> takes a user-supplied equality predicate." A precondition is that the
> user-supplied predicate is an equality predicate. (>=) is not an equality
> predicate, be it in the layperson sense of "it isn't analogous to (==)" or
> the
> mathematical sense of "it isn't an equivalence relation".
> 

-- 
View this message in context: 
http://old.nabble.com/whine-and-solution-about-programmers-not-respecting-documentations-tp29017296p29021467.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Lars Viklund
On Mon, Jun 28, 2010 at 07:44:34PM +, Albert Y.C.Lai wrote:
> I propose that at each minor version of base, someone picks an implementation
> randomly.
> 
> Here is a more radical, less labour-intensive solution, if you don't mind a
> judicious, correctness-preserving use of unsafePerformIO: at the first
> invocation of the process lifetime, pick an implementation randomly.

Over in ##c++, there is sometimes talk about an Evil Standard Library,
that attempts to do interesting things in response to any undefined
or implementation defined behaviour, triggering things like launching
NetHack.

-- 
Lars Viklund | z...@acc.umu.se
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Edward Z. Yang
Excerpts from Albert Y.C.Lai's message of Mon Jun 28 15:44:34 -0400 2010:
> I propose that at each minor version of base, someone picks an implementation
> randomly.

This has actually been done, in a legitimate language implementation.
Check out:

http://web.mit.edu/~axch/www/scheme/choices/non-ascii-integer-to-char.html

Scheme 48, iirc, adds 1000 to the integer value of an ASCII character.

Cheers,
Edward
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Ketil Malde
Albert Y.C.Lai  writes:

> The doc of deleteBy states: "The deleteBy function behaves like delete, but
> takes a user-supplied equality predicate." A precondition is that the
> user-supplied predicate is an equality predicate. (>=) is not an equality
> predicate, be it in the layperson sense of "it isn't analogous to (==)" or the
> mathematical sense of "it isn't an equivalence relation".
  
One could argue that this is a bad specification.  The type is

  deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]

but there are further limitations on the arguments, and worse, the function
doesn't check this and produce an error if the arguments don't conform,
but just silently produces a meaningless result.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Mark Lentczner

On Jun 28, 2010, at 2:29 PM, Luke Palmer wrote:

> I proposed the following solution:
> 
> http://lukepalmer.wordpress.com/2009/07/01/on-the-by-functions/

Seconded! I always want xxxOn and I almost never (perhaps never*) want xxxBy 
for xxx in sort, maximum, group and nub.

- Mark

(*) A quick scan of all the Haskell source I wrote on my machine reveals that I 
have never once used xxxBy without giving it a function of the form "(==) on 
foo" or "comparing foo"!


Mark Lentczner
http://www.ozonehouse.com/mark/
IRC: mtnviewmark



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Roman Beslik

 In the case of 'deleteBy' we can improve an API.
  deleteBy eq x xs == deletePred (eq x) xs
@deletePred pred xs@ removes the first element of @xs@ which satisfies a 
predicate @p...@.

Your solution is more general. :)

On 28.06.10 22:44, Albert Y.C.Lai wrote:

And then some programmers are in a miserable state of not respecting docs
when the docs are complete.

Why should anyone expect

   deleteBy (>=) 5 [0..10]


--
Best regards,
  Roman Beslik.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Luke Palmer
On Mon, Jun 28, 2010 at 1:44 PM, Albert Y.C.Lai  wrote:
> Why should anyone expect
>
>  deleteBy (>=) 5 [0..10]
>
> to accomplish anything meaningful, if he/she respects the written docs?

I proposed the following solution:

http://lukepalmer.wordpress.com/2009/07/01/on-the-by-functions/



>
> Today someone on #haskell expected it to accomplish something meaningful,
> even something mind-reading. The said person has been around for more than
> a year, not eligible for the "newbie" excuse. The said person is just the
> tip of an iceberg.
>
> The doc of deleteBy states: "The deleteBy function behaves like delete, but
> takes a user-supplied equality predicate." A precondition is that the
> user-supplied predicate is an equality predicate. (>=) is not an equality
> predicate, be it in the layperson sense of "it isn't analogous to (==)" or the
> mathematical sense of "it isn't an equivalence relation".
>
> If you respect the precondition or the authors of the doc, you should just
> never use deleteBy (>=) 5 [0..10], much less expect any meaningful result.
>
> I propose this solution:
>
> For each of deleteBy, groupBy, unionBy... we can usually conceive at least two
> implementations, behaving pretty much the same (answer, speed, space) when
> given an equivalence relation (modulo some rare concern when the equivalence
> relation has assymetric strictness properties), but behaving different when
> not, and their code sizes are pretty much the same. With more imagination and
> allowing some code bloat, perhaps we can conceieve more implementations. But
> two suffices, really.
>
> I propose that at each minor version of base, someone picks an implementation
> randomly.
>
> Here is a more radical, less labour-intensive solution, if you don't mind a
> judicious, correctness-preserving use of unsafePerformIO: at the first
> invocation of the process lifetime, pick an implementation randomly.
>
> The result frustrates people who disrespect the docs. My purpose is exactly
> that. The goal is to give people an incentive to not disrepect the docs.
>
> (If you think this is a nasty "stick, not carrot" incentive, on first thought 
> I
> would agree. On second thought, it is not adding a stick, it is just removing 
> a
> carrot. Programmer's carrot means his/her code "works" consistently. When
> deleteBy (>=) "works" consistently, you are giving out undeserved free carrots
> --- incentive to write more wrong code. I am proposing to remove undeserved
> free carrots.)
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-28 Thread Albert Y . C . Lai
Some docs are in a miserable state of being incomplete.

And then some programmers are in a miserable state of not respecting docs
when the docs are complete.

Why should anyone expect

  deleteBy (>=) 5 [0..10]

to accomplish anything meaningful, if he/she respects the written docs?

Today someone on #haskell expected it to accomplish something meaningful,
even something mind-reading. The said person has been around for more than
a year, not eligible for the "newbie" excuse. The said person is just the
tip of an iceberg.

The doc of deleteBy states: "The deleteBy function behaves like delete, but
takes a user-supplied equality predicate." A precondition is that the
user-supplied predicate is an equality predicate. (>=) is not an equality
predicate, be it in the layperson sense of "it isn't analogous to (==)" or the
mathematical sense of "it isn't an equivalence relation".

If you respect the precondition or the authors of the doc, you should just
never use deleteBy (>=) 5 [0..10], much less expect any meaningful result.

I propose this solution:

For each of deleteBy, groupBy, unionBy... we can usually conceive at least two
implementations, behaving pretty much the same (answer, speed, space) when
given an equivalence relation (modulo some rare concern when the equivalence
relation has assymetric strictness properties), but behaving different when
not, and their code sizes are pretty much the same. With more imagination and
allowing some code bloat, perhaps we can conceieve more implementations. But
two suffices, really.

I propose that at each minor version of base, someone picks an implementation
randomly.

Here is a more radical, less labour-intensive solution, if you don't mind a
judicious, correctness-preserving use of unsafePerformIO: at the first
invocation of the process lifetime, pick an implementation randomly.

The result frustrates people who disrespect the docs. My purpose is exactly
that. The goal is to give people an incentive to not disrepect the docs.

(If you think this is a nasty "stick, not carrot" incentive, on first thought I
would agree. On second thought, it is not adding a stick, it is just removing a
carrot. Programmer's carrot means his/her code "works" consistently. When
deleteBy (>=) "works" consistently, you are giving out undeserved free carrots
--- incentive to write more wrong code. I am proposing to remove undeserved
free carrots.)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe