I disagree that it's a wart. The wart is that we don't *also* have an Ord version. nub/nubBy have two great properties. (1) They only require Eq. (2) They are lazier than their Ord-using counterparts.
Same indifference here, what does "remove duplicates according to relation R" mean intuitively if R is not an equivalence relation?
(nub and nubBy with their quadratic complexity are anyway a wart. These names should ideally be used for versions that only work for lists over ordered type, so that one can give an implementation with a sensible complexity.)
But do if you must.
On 24.09.2014 01:45, Dan Doel wrote:
nub and nubBy already obey the semantics of the Haskell 2010 report,
which only specifies the behavior when you pass it an "equality test,"
presumably an equivalence relation.
The Haskell 98 report similarly specified nubBy as assuming the function
passed in defined an equivalence. So the current definition is not
actually in violation of that spec, either. Rather, 'nubBy (<)' is
calling the function with an invalid argument.
I'm ambivalent about whether this gets 'fixed', but it is technically
not a bug (or, the only definitive error is that the comment doesn't
match the implementation).
-- Dan
On Tue, Sep 23, 2014 at 5:45 PM, Thomas Miedema <thomasmiedema@gmail.com
<mailto:thomasmiedema@gmail.com>> wrote:
The implementation of nubBy in Data.List is as follows, where
USE_REPORT_PRELUDE refers to [1]:
#ifdef USE_REPORT_PRELUDE
nubBy eq [] = []
nubBy eq (x:xs) = x : nubBy eq (filter (\ y -> not (eq
x y)) xs)
#else
nubBy eq l = nubBy' l []
where
nubBy' [] _ = []
nubBy' (y:ys) xs
| elem_by eq y xs = nubBy' ys xs
| otherwise = y : nubBy' ys (y:xs)
-- Not exported:
-- Note that we keep the call to `eq` with arguments in the
-- same order as in the reference implementation
-- 'xs' is the list of things we've seen so far,
-- 'y' is the potential new element
elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
elem_by _ _ [] = False
elem_by eq y (x:xs) = y `eq` x || elem_by eq y xs
#endif
That comment is actually not correct [2], and the report version and
the base
version don't have the same semantics when used on asymmetric relations:
MyReportPrelude> nubBy (<) [1]
[1]
Data.List> nubBy (<) [1,2]
[1,2]
## Proposal
Make nubBy and nub obey the report semantics by swapping the
arguments to
`eq` in elem_by, and defining nub as nubBy (==). This is the 'still
easy'
variant from [3].
## Motivation
The Report's order is more sensible, since the parameters to the
relation stay
in the left-to-right order in which they occurred in the list. See
[4,5] for
user bug reports.
Discussion period: 2 weeks
Code review: https://phabricator.haskell.org/D238
[1] https://www.haskell.org/onlinereport/list.html#sect17.6
[2] https://ghc.haskell.org/trac/ghc/ticket/2528
[3] https://ghc.haskell.org/trac/ghc/ticket/7913#comment:3
[4] https://ghc.haskell.org/trac/ghc/ticket/3280
[5] https://ghc.haskell.org/trac/ghc/ticket/7913
_______________________________________________
Libraries mailing list
Libraries@haskell.org <mailto:Libraries@haskell.org>
http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries
--
Andreas Abel <>< Du bist der geliebte Mensch.
Department of Computer Science and Engineering
Chalmers and Gothenburg University, Sweden
andreas.abel@gu.se
http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries