Proposal for generalized function partition in List-library

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
17 May 2001 19:36:44 GMT


Thu, 17 May 2001 10:06:55 +0200, Bernd Holzmüller <holzmueller@ics-ag.de> pisze:

> I would like to propose a new function for module List that generalizes
> the current function partition :: (a -> Bool) -> [a] -> [[a]]

No, current partition has type (a -> Bool) -> [a] -> ([a], [a])
so your function is not compatible with it, so shouldn't replace such
standard function.

> partition:: Eq b => (a -> b) -> [a] -> [[a]]
> partition _ [] = []
> partition f (a:as) = 
>    let  (as',as'') = foldr (select (f a)) ([],[]) as
>    in   (a:as'):partition f as''
>  where
>    select b x (ts,fs) | f x == b  = (x:ts,fs)
> 		      | otherwise = (ts,x:fs)

This function doesn't give a hint which sublists correspond to which
results of the function, so I'm afraid it's easy to make errors
by assuming that they will come in a different order. And it's
inefficient: the cost is the number of elements times the number of
different results of the function.

I would write it thus:
    \f xs -> groupBy (\(a, _) (b, _) -> a == b) $
             sortBy  (\(a, _) (b, _) -> compare a b)
             [(f x, x) | x <- xs]
You can apply 'map (map snd)' to the result to remove the results of f.
I don't have a good name for it and I'm not sure it's common enough to
put it in the standard library.

It can also be more efficiently written using Array.accumArray for
particular types of the result of the function.


PS. What I would perhaps put into standard library:
    uniq   :: Eq a => [a] -> [a]
    uniqBy :: (a -> a -> Bool) -> [a] -> [a]
so people don't use nub unnecessarily (if elements are adjacent or
can be made adjacent by sorting), and
    takeLastWhile :: (a -> Bool) -> [a] -> [a]
    dropLastWhile :: (a -> Bool) -> [a] -> [a]
    spanEnd       :: (a -> Bool) -> [a] -> ([a], [a])
(with some better names) which iterate forward and are lazy, to avoid
double reversing in case the test is cheap but the list is long, and
    partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])

Here are implementations of some of these:

    takeLastWhile p xs = case span p xs of
        (ys, [])   -> ys
        (_,  _:zs) -> takeLastWhile p zs

    dropLastWhile p xs = case span p xs of
        (_,  [])   -> []
        (ys, z:zs) -> ys ++ z : dropLastWhile p zs

    spanEnd p xs = case span p xs of
        (ys, [])   -> ([], ys)
        (ys, z:zs) -> (ys ++ z : ys', zs')
                      where (ys', zs') = spanEnd p zs

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK