where to put handy functions?

Is there process for submitting functions for consideration for inclusion into future versions of the standard libraries? For example, I'd like to see this in Data.List: extract :: [Int] -> [a] -> [a] extract = f 0 where f _ _ [] = [] f _ [] _ = [] f k nss@(n:ns) (x:xs) = if n == k then x:f (k+1) ns xs else f (k+1) nss xs This behaves roughly as extract ns xs == map (xs !!) ns except that it's a lot more efficient, and it still works if ns or xs (but not both) are infinite. Oh, and "ns" are required to be ordered and non-negative. I'm guessing there are a lot of similarly simple handy functions, and I'm wondering if there's anything in place to avoid (1) reinventing the wheel, and (2) name clashes. Someone else may have written "extract" as well, meaning one of us wasted our time. And chances are, if they did, it has a different name, leading to forced qualified imports. Finally, even if no one else is using it, it would be good to settle on reasonable names for things more easily. Is there a better name for this function? Is there a reason not to call it "extract"? -- Chad Scherrer "Time flies like an arrow; fruit flies like a banana" -- Groucho Marx

On Thu, Aug 09, 2007 at 02:29:50PM -0700, Chad Scherrer wrote:
Is there process for submitting functions for consideration for inclusion into future versions of the standard libraries? For example, I'd like to see this in Data.List:
extract :: [Int] -> [a] -> [a] extract = f 0 where f _ _ [] = [] f _ [] _ = [] f k nss@(n:ns) (x:xs) = if n == k then x:f (k+1) ns xs else f (k+1) nss xs
This behaves roughly as extract ns xs == map (xs !!) ns
except that it's a lot more efficient, and it still works if ns or xs (but not both) are infinite. Oh, and "ns" are required to be ordered and non-negative.
I'm guessing there are a lot of similarly simple handy functions, and I'm wondering if there's anything in place to avoid (1) reinventing the wheel, and (2) name clashes. Someone else may have written "extract" as well, meaning one of us wasted our time. And chances are, if they did, it has a different name, leading to forced qualified imports.
Finally, even if no one else is using it, it would be good to settle on reasonable names for things more easily. Is there a better name for this function? Is there a reason not to call it "extract"?
http://www.haskell.org/haskellwiki/Library_submissions Stefan

On 10 Aug 2007, at 9:37 am, Stefan O'Rear wrote:
I'd like to ask if it's possible to add expm1 and log1p to the Floating class: class ... Floating a where ... exp, log, sqrt :: a -> a expm1, lop1p :: a -> a -- new, copied from C99 ... expm1 x = exp x - 1 -- but done more accurately log1p x = log (1 + x) -- but done more accurately However, the Library_submissions page wants an implementation, and adding this sort of function seems to require getting into the guts of an implementation. (Difficult: I am having serious trouble getting GHC 6.6 to install at all, never mind changing it.)

On 8/9/07, Chad Scherrer
extract :: [Int] -> [a] -> [a] extract = f 0 where f _ _ [] = [] f _ [] _ = [] f k nss@(n:ns) (x:xs) = if n == k then x:f (k+1) ns xs else f (k+1) nss xs
This behaves roughly as extract ns xs == map (xs !!) ns
except that it's a lot more efficient, and it still works if ns or xs (but not both) are infinite. Oh, and "ns" are required to be ordered and non-negative.
Nifty function there. =) And for the record, it works just fine if both lists are infinite -- it just produces an infinite output list, but it's lazy so no problem: *Main> take 10 $ extract [1,3..] [2..] [3,5,7,9,11,13,15,17,19,21] -Brent

On 8/9/07, Chad Scherrer
Is there process for submitting functions for consideration for inclusion into future versions of the standard libraries? For example, I'd like to see this in Data.List:
I imagine including it in std lib takes a while. Would it be a good idea to include it in MissingH http://software.complete.org/missingh in the mean time? Cheers, Rahul

rk:
On 8/9/07, Chad Scherrer
wrote: Is there process for submitting functions for consideration for inclusion into future versions of the standard libraries? For example, I'd like to see this in Data.List:
I imagine including it in std lib takes a while. Would it be a good idea to include it in MissingH http://software.complete.org/missingh in the mean time?
It is probably better not to stick everything in MissingH -- its too big to be used easily. Smaller packages (say, Data.List.Extensions) make more sense. However, getting ok for stuff in Data.List isn't too hard. Just follow the libraries submission process: http://haskell.org/haskellwiki/Library_submissions Cheers, Don

On 8/9/07, Chad Scherrer
extract :: [Int] -> [a] -> [a] extract = f 0 where f _ _ [] = [] f _ [] _ = [] f k nss@(n:ns) (x:xs) = if n == k then x:f (k+1) ns xs else f (k+1) nss xs
Finally, even if no one else is using it, it would be good to settle
on reasonable names for things more easily. Is there a better name for this function? Is there a reason not to call it "extract"?
Other possible names which occur to me include select, slice, mask. I think I like 'select' best myself, but 'extract' works too. Amusingly, extract is intimately related to function composition. Suppose we have listify :: (Int -> Int) -> [Int] listify = flip map [0..] Then if f, g :: Int -> Int, and f is monotonically increasing, we have the identity (listify f) `extract` (listify g) = listify (g . f) This randomly occurred to me as I was falling asleep last night and I thought I would share. =) -Brent

Hmm, this would make a good QuickCheck property. I wonder, is listify
a contravariant functor? Fun to work through the details of that some
time, I think.
Chad
On 8/10/07, Brent Yorgey
Amusingly, extract is intimately related to function composition. Suppose we have
listify :: (Int -> Int) -> [Int] listify = flip map [0..]
Then if f, g :: Int -> Int, and f is monotonically increasing, we have the identity
(listify f) `extract` (listify g) = listify (g . f)
This randomly occurred to me as I was falling asleep last night and I thought I would share. =)
-Brent

Chad Scherrer wrote:
I wonder, is listify a contravariant functor?
I wonder - will I ever reach the stage where I too make off-hand remarks like this? :-} Now I know how all the "normal" people feel when I tell them that a relation is simply a subset of the extended Cartesian product of the respective domains of its attributes...

Chad Scherrer wrote:
extract :: [Int] -> [a] -> [a]
[...]
This behaves roughly as extract ns xs == map (xs !!) ns
extract sounds like removing the elements to be extracted from the original list. I would therefore expect it's type signature to be extract :: [Int] -> [a] -> ([a], [a]) with extract [0, 2] "abcde" == ("ac", "bde"). For your extract I would prefer "select" as name, in analogy to relational algebra, viewing a list as a one-column table.
Oh, and "ns" are required to be ordered and non-negative.
Non-negative is obvious for a list of indexes. Ordered makes sense implementation-wise, and should be easy to match for many applications. But is it a sensible constraint on a standard library function? For Data.List, I would prefer a multi-pass select function like this: select :: Integral n => [n] -> [a] -> [a] select ns xs = select' 0 ns xs where select' k [] _ = [] select' k (n:ns) [] = select' k ns [] select' k nns@(n:ns) yys@(y:ys) = case k `compare` n of LT -> select' (succ k) nns ys EQ -> y : select' k ns yys GT -> select nns xs *Main> select [0, 2, 2, 1] "abcde" "accb" There could be selectAsc for the special case of ordered indexes, to avoid keeping the whole input list in memory. Tillmann

Agreed. I like "select" better too, and the regular vs "Asc" version
is a nice parallel with fromList and fromAscList.
Chad
On 8/10/07, Tillmann Rendel
Non-negative is obvious for a list of indexes. Ordered makes sense implementation-wise, and should be easy to match for many applications. But is it a sensible constraint on a standard library function?
For Data.List, I would prefer a multi-pass select function like this:
select :: Integral n => [n] -> [a] -> [a] select ns xs = select' 0 ns xs where select' k [] _ = [] select' k (n:ns) [] = select' k ns [] select' k nns@(n:ns) yys@(y:ys) = case k `compare` n of LT -> select' (succ k) nns ys EQ -> y : select' k ns yys GT -> select nns xs
*Main> select [0, 2, 2, 1] "abcde" "accb"
There could be selectAsc for the special case of ordered indexes, to avoid keeping the whole input list in memory.
Tillmann

Posix has pretty well taken the name "select." It probably isn't a good idea to use that name in a commonly imported library like Data.List, since users will have to mask and qualify it if they also import Posix libraries. -- Brian T. Sniffen bts@alum.mit.edu or brian.sniffen@gmail.com http://www.evenmere.org/~bts
participants (9)
-
Andrew Coppin
-
Brent Yorgey
-
Brian Sniffen
-
Chad Scherrer
-
dons@cse.unsw.edu.au
-
ok
-
Rahul Kapoor
-
Stefan O'Rear
-
Tillmann Rendel