Proposal (Trac ticket #3671): Add takeRec, genericTakeRec and spanRec to Data.List

Dear all, After defining these for the umpeenth time, I would like to add the functions takeRec, genericTakeRec and spanRec to Data.List, as per http://hackage.haskell.org/trac/ghc/ticket/3671 Suggested discussion time: 2 weeks. Regards, Philip

Hi Philip, On Tue, Nov 17, 2009 at 02:47:44PM +0100, Philip K.F. Hölzenspies wrote:
After defining these for the umpeenth time, I would like to add the functions takeRec, genericTakeRec and spanRec to Data.List, as per
I don't think spanRec does what you want: take 10 $ spanRec (< 3) [1,2,3,4,5,6,1,2,3,4,5,6] [[1,2],[],[],[],[],[],[],[],[],[]] I have also defined your "takeRec" a number of times in the past, but I have called it something like "splitAts". I've also defined functions called "breaks". I think the 's' suffix is more consistent with "tails", "inits" etc. Thanks Ian

On Tue, 2009-11-17 at 14:35 +0000, Ian Lynagh wrote:
I don't think spanRec does what you want:
take 10 $ spanRec (< 3) [1,2,3,4,5,6,1,2,3,4,5,6] [[1,2],[],[],[],[],[],[],[],[],[]]
I have also defined your "takeRec" a number of times in the past, but I have called it something like "splitAts". I've also defined functions called "breaks". I think the 's' suffix is more consistent with "tails", "inits" etc.
Dear Ian, et al. I posted the proposal too quickly. Two corrections and *still* missed it. I should have dug up my PreludeEx from somewhere. You are right about the mistake, though. Also, I also usually use the 's' suffix, but thought it could possibly be considered too invasive in the namespace. If no one objects to +s names, then I actually prefer it. When also including spans antonym 'breaks', they can actually be defined in mutually recursive fashion. Thus, the new proposal: splitAts :: Int -> [a] -> [[a]] splitAts = genericSplitAts genericSplitAts :: (Integral a) => a -> [b] -> [[b]] genericSplitAts n _ | n <= 0 = [] genericSplitAts _ [] = [] genericSplitAts i xs = let (hs,ts) = genericSplitAt i xs in hs : genericSplitAts i ts spans :: (a -> Bool) -> [a] -> [[a]] spans _ [] = [] spans p xs = let (hs,ts) = span p xs in hs : breaks p ts breaks :: (a -> Bool) -> [a] -> [[a]] breaks _ [] = [] breaks p xs = let (hs,ts) = break p xs in hs : spans p ts Am I chalking you up as a +1? Regrads, Philip

On Tue, Nov 17, 2009 at 04:11:21PM +0100, Philip K.F. Hölzenspies wrote:
Am I chalking you up as a +1?
For splitAts, yes. My breaks has generally been such that breaks "123,456,,78" == ["123", "456", "", "78"] but the details probably depend on exactly what I've been using it for. I don't remember ever needing yours. I'd have thought that breaks :: (a -> Bool) -> [a] -> [([a], [a])] would make more sense, but personally I'd vote for not adding a breaks at all. Thanks Ian

On Wed, Nov 18, 2009 at 3:47 PM, Ian Lynagh
On Tue, Nov 17, 2009 at 04:11:21PM +0100, Philip K.F. Hölzenspies wrote:
Am I chalking you up as a +1?
For splitAts, yes.
My breaks has generally been such that breaks "123,456,,78" == ["123", "456", "", "78"] but the details probably depend on exactly what I've been using it for.
I've been using this kind of breaks as well in the past. Is there a usecase for a more general version? Apart from that I'm positive towards the groupsOf function. Josef

On Thu, Nov 19, 2009 at 11:11:08AM +0100, Josef Svenningsson wrote:
On Wed, Nov 18, 2009 at 3:47 PM, Ian Lynagh
wrote: On Tue, Nov 17, 2009 at 04:11:21PM +0100, Philip K.F. Hölzenspies wrote:
Am I chalking you up as a +1?
For splitAts, yes.
My breaks has generally been such that breaks "123,456,,78" == ["123", "456", "", "78"] but the details probably depend on exactly what I've been using it for.
I've been using this kind of breaks as well in the past. Is there a usecase for a more general version?
Ooops, I actually meant breaks (',' ==) "123,456,,78" == ["123", "456", "", "78"] but personally I don't think this should be standardised. Thanks Ian

Ian Lynagh wrote:
breaks (',' ==) "123,456,,78" == ["123", "456", "", "78"]
Yes, that is very useful, and we get the other semantics from "runs". So as of now, I am leaning towards: runs = groupBy . on (==) spans p = filter (p . head) . runs p breaks p = filter (not . p . head) . runs p
but personally I don't think this should be standardised.
All of these functions are very simple combinations of existing ones. On the other hand, it took us until now to realize that, so I'm not sure. In any case, I definitely would like to see groupsOf (or a rose by any other name) in the library. Thanks, Yitz

Ian Lynagh wrote:
breaks (',' ==) "123,456,,78" == ["123", "456", "", "78"]
I wrote:
runs = groupBy . on (==) breaks p = filter (not . p . head) . runs p
Except that has slightly different semantics than Ian's: breaks (',' ==) "123,456,,78" == ["123","456","78"] -Yitz

Ian Lynagh wrote:
breaks (',' ==) "123,456,,78" == ["123", "456", "", "78"]
I wrote:
runs = groupBy . on (==) breaks p = filter (not . p . head) . runs p
Except that has slightly different semantics than Ian's: breaks (',' ==) "123,456,,78" == ["123","456","78"]
A combinator approach to Ian's semantics: spans p = map (takeWhile p) . takeWhile (not . null) . iterate (drop 1 . dropWhile p) breaks p = spans $ not . p Here you have to put the "not null" step in the middle. I wonder if that interferes with the fusion. -Yitz

Philip K.F. Hölzenspies wrote:
After defining these for the umpeenth time, I would like to add the functions takeRec, genericTakeRec and spanRec to Data.List, as per http://hackage.haskell.org/trac/ghc/ticket/3671
Ian Lynagh wrote:
I have also defined your "takeRec" a number of times in the past, but I have called it something like "splitAts".
I've been using it for years, under the name "groupsOf" - which is also consistent with Data.List naming conventions, and a bit less confusing than "splitAts" in my opinion. Another reason I don't use splitAts is that I don't use splitAt in its definition anymore; I've come to prefer groupsOf n = takeWhile (not . null) . map (take n) . iterate (drop n) In fact, I use this function so much that I put it in my dot-ghci so it will always be at my fingertips. I am very much in favor of adding it to Data.List. Regards, Yitz

groupsOf n = takeWhile (not . null) . map (take n) . iterate (drop n)
+1 for the name. Nice combinator-based definition too. (How does its performance compare to a directly recursive defn??) Regards, Malcolm

Hello Malcolm, Thursday, November 19, 2009, 4:15:17 AM, you wrote:
groupsOf n = takeWhile (not . null) . map (take n) . iterate (drop n)
+1 for the name. Nice combinator-based definition too. (How does its performance compare to a directly recursive defn??)
take+drop combination should be slower than splitAt -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

take+drop combination should be slower than splitAt
I suppose the only convincing argument is empirical. Using the following simple and unscientific benchmark, it turns out that take +drop is ~ 2x faster than splitAt. Maybe list fusion or something is kicking in. main = do print (length (splitAts 15 bigList)) main' = do print (length (groupsOf 15 bigList)) bigList = replicate 15000000 () groupsOf n = takeWhile (not . null) . map (take n) . iterate (drop n) splitAts n [] = [] splitAts n xs = let (a,b) = splitAt n xs in a: splitAts n b time ./groupsOf 1000000 real 0m0.234s user 0m0.225s sys 0m0.006s time ./splitAts 1000000 real 0m0.557s user 0m0.542s sys 0m0.012s Regards, Malcolm

Dear Malcolm, Ian, et al. On Thu, 2009-11-19 at 04:14 +0000, Malcolm Wallace wrote:
I suppose the only convincing argument is empirical.
Hear, hear! Although... the empirical argument changes with the versions of the compiler. Anyone up for an evaluation of alternative implementations of all functions in base? :p
Using the following simple and unscientific benchmark, it turns out that take +drop is ~ 2x faster than splitAt. Maybe list fusion or something is kicking in.
Is it possible that the tuple wrapping and unwrapping in the splitAt-implementation hurts optimization? On Wed, 2009-11-18 at 14:47 +0000, Ian Lynagh wrote:
My breaks has generally been such that breaks "123,456,,78" == ["123", "456", "", "78"] but the details probably depend on exactly what I've been using it for.
I don't remember ever needing yours. I'd have thought that breaks :: (a -> Bool) -> [a] -> [([a], [a])] would make more sense, but personally I'd vote for not adding a breaks at all.
The more I looked at the spans/breaks, the more I figured that didn't quite cover the majority of cases for which I hack in extra functionality. I think I have it down to the bare bones of what I was missing; there's no function in Data.List to segment a list based on sequence properties. In other words, there is no way to extract runs (or clumps, if you prefer). An alternative suggestion, thus: runs :: (a -> a -> Bool) -> [a] -> [[a]] runs p xs = ... which produces a list of runs, i.e. the first result is that prefix of xs, such that for all consecutive elements e_i, e_{i+1}, the property holds, i.e. p e_i e_{i+1} -->> True. Although not exactly equivalent, spans' can be implemented as: spans' p = runs (\x y -> p x == p y) the difference being the first span:
spans odd [2,3,4,5,7,9,8,0,3,5,9] [[],[2],[3],[4],[5,7,9],[8,0],[3,5,9]] spans' odd [2,3,4,5,7,9,8,0,3,5,9] [[2],[3],[4],[5,7,9],[8,0],[3,5,9]]
This difference is of no consequence to the types of programs I used spans in. This new implementation makes spans so simple that inclusion in Data.List is no longer necessary. So my new proposal would be to include groupsOf and runs. Now for the empirical stuff. I have two implementations: runs :: (a -> a -> Bool) -> [a] -> [[a]] runs _ [ ] = [] runs _ [x] = [[x]] runs p (x:xs) = r : runs p xs' where (r,xs') = run x xs cons' x (xs,y) = (x:xs,y) run y [] = ([y],[]) run y l@(x:xs) | p y x = cons' y $ run x xs | otherwise = ([y],l) runsAlt :: (a -> a -> Bool) -> [a] -> [[a]] runsAlt _ [] = [[]] runsAlt _ xs@[x] = [xs] runsAlt p (x:xs@(y:_)) | p x y = (x : head xs') : tail xs' | otherwise = [x]:xs' where xs' = runsAlt p xs (I welcome suggestions for improvements.) Used in the program: bigList = concat $ replicate 10000000 [5,6,9,1,3,4,2] main = print (length (runs (>) bigList)) compiled without and with -O2: runs : 5.40s user 0.03s system 99% cpu 5.438 total runsOpt : 4.40s user 0.03s system 99% cpu 4.440 total runsAlt : 4.89s user 0.04s system 99% cpu 4.934 total runsAltOpt : 4.14s user 0.03s system 99% cpu 4.207 total We have a winner ;) Regards, Philip

Philip K.F. wrote:
runs :: (a -> a -> Bool) -> [a] -> [[a]] runs p xs = ...
which produces a list of runs, i.e. the first result is that prefix of xs, such that for all consecutive elements e_i, e_{i+1}, the property holds, i.e. p e_i e_{i+1} -->> True.
We already have something like that: groupBy :: (a -> a -> Bool) -> [a] -> [[a]] In fact, instead of spans and breaks, why not just use: runs :: (a -> Bool) -> [a] -> [[a]] runs = groupBy . on (==) Then we have: breaks p = runs p . dropWhile p spans p = runs p . dropWhile (not . p) Regards, Yitz

On Thu, 2009-11-19 at 13:28 +0200, Yitzchak Gale wrote:
Philip K.F. wrote:
runs :: (a -> a -> Bool) -> [a] -> [[a]] runs p xs = ...
which produces a list of runs, i.e. the first result is that prefix of xs, such that for all consecutive elements e_i, e_{i+1}, the property holds, i.e. p e_i e_{i+1} -->> True.
We already have something like that:
groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
The groupBy function compares the first element e_1 to all consecutive elements e_i until it finds one for which the predicate doesn't hold. The runs function compares *consecutive* elements e_i and e_{i+1}. By example:
runs (<) [1,2,3,4,3,4,5] [[1,2,3,4],[3,4,5]]
In fact, instead of spans and breaks, why not just use:
runs :: (a -> Bool) -> [a] -> [[a]] runs = groupBy . on (==)
groupBy . on (==) :: (a -> ()) -> [a] -> [[a]]
Then we have:
breaks p = runs p . dropWhile p spans p = runs p . dropWhile (not . p)
For spans and breaks there might be a composition of functions already in Data.List, but because of the above type check failure, it's not this. Also, runs is more general than spans and breaks and runs is actually more sorely missed. I may still be mistaken, but there are no functions in Data.List that allow predicates on *consecutive* list elements. Regards, Philip

On Thu, 2009-11-19 at 15:02 +0100, Philip K.F. Hölzenspies wrote:
runs :: (a -> Bool) -> [a] -> [[a]] runs = groupBy . on (==)
groupBy . on (==) :: (a -> ()) -> [a] -> [[a]]
Don't know what neuron misfired there... my apologies. I quickly tried it out in ghci:
let runs' = groupBy . on (==) :t runs' x :: (a -> ()) -> [a] -> [[a]]
but of course:
:t groupBy . on (==) groupBy . on (==) :: (Eq b) => (a -> b) -> [a] -> [[a]]
My bad. However, runs is still considerably more general and, AFAICT, not a composition of other Data.List functions. I agree with Ian that even if it took us a while to write those compositions properly, they shouldn't be in the library. I stand by runs, though ;) Regards, Philip

My proposal would be to add a function like \begin{code} replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] replaceBy splt l = case l of [] -> [] _ -> let (ft, rt) = splt l in ft : replaceBy splt rt \end{code} that takes a function "splt" that splits a non-empty list and returns a shorter list as second component (to ensure termination). I've used this function to implement a replace function (below), but the simplest application is: \begin{code} splitAts :: Int -> [a] -> [[a]] splitAts n | n > 0 = replaceBy (splitAt n) \end{code} or with Control.Applicative: \begin{code} breaks :: (a -> Bool) -> [a] -> [[a]] breaks p = replaceBy $ second (drop 1) . break p \end{code} This "breaks" function ignores a final separator! breaks (',' ==) "123,456,,78" == ["123","456","","78"] breaks (',' ==) "123,456,78," == ["123","456","78"] groupBy could be implemented as follows: \begin{code} groupBy eq = replaceBy $ \ (h : r) -> first (h :) $ span (eq h) r \end{code} And given a function to split of a single "run", "runs" (with the same type as groupBy) is simply: \begin{code} runs :: (a -> a -> Bool) -> [a] -> [[a]] runs eq = replaceBy (run eq) run :: (a -> a -> Bool) -> [a] -> ([a], [a]) run eq l = case l of x : r@(y : s) | eq x y -> first (x :) $ run eq r x : r -> ([x], r) [] -> ([], []) \end{code} My original application for replacing a substring by a special character is defined by: \begin{code} replace :: Eq a => [a] -> a -> [a] -> [a] replace sl@(_ : _) r = replaceBy $ \ l@(hd : tl) -> case stripPrefix sl l of Nothing -> (hd, tl) Just rt -> (r, rt) \end{code} Cheers Christian

Christian Maeder wrote:
My proposal would be to add a function like
\begin{code} replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] replaceBy splt l = case l of [] -> [] _ -> let (ft, rt) = splt l in ft : replaceBy splt rt \end{code}
that takes a function "splt" that splits a non-empty list and returns a shorter list as second component (to ensure termination).
.... if we're in the business of proposing generalised search and replace I'd like to propose this one: http://haskell.org/pipermail/haskell-cafe/2007-July/028032.html which is along the general lines above but slightly more general. When I made that posting in 2007 I was hoping for name suggestions. In the absence of anythign better I suggest 'Data.List.transform' or the more whimsical 'Data.List.transmogrify'. I would also suggest a convenience function 'Data.List.replace' defined from it in the obvious way. I am also in agreement with 'groupsOf' (which I sometimes called 'chunksOf' but I like both names) proposed by Yitzchak. Will all that in mind I oppose this proposal, because whilst I fully support filling in some gaps in Data.List I don't think these are the best primitives. Jules

Ok, lets try to get back to the proposal. 1. We want something like takeRec being named splitAts or groupsOf (groupsOf is too similar to the existing groupsBy) 2. genericTakeRec is just a variant of takeRec based on genericSplitAt rather than splitAt (or genericTake, genericDrop instead of take, drop) 3. spanRec changed to a mutual recursive implementation for spans and breaks (in the ticket) that is not supported much. Rather breaks was more discussed in this thread as a splitting function (that was discussed years before under splitBy or splitOn without any agreement.) Agreement seems to be about "breaks p = spans (not . p)" (or vice versa) Furthermore, proposal for runs (4.) and replace (5.) came up in this thread, that are not part of the ticket. 4. I find "runs" useful in the sense proposed by Philip with type runs :: (a -> a -> Bool) -> [a] -> [[a]]
runs (<) [1,2,3,4,3,4,5] [[1,2,3,4],[3,4,5]]
(there's no proposal to rename groupsBy) 5. The type of my replace function was: replace :: Eq a => [a] -> a -> [a] -> [a] and a (reasonable) alternative would be to replace a sublist by another sublist and not by a single element. Which of the above functions (1. - 4.) should be part of the proposal? How should these functions be implemented? I only made a proposal how they could be implemented using replaceBy (below), but direct recursive definitions may be more appropriate. I.e. unlines and unwords are also defined with explicit recursion although alternative definitions are there (based on concatMap and foldr1) Cheers Christian Jules Bean schrieb:
Christian Maeder wrote:
My proposal would be to add a function like
\begin{code} replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] replaceBy splt l = case l of [] -> [] _ -> let (ft, rt) = splt l in ft : replaceBy splt rt \end{code}
that takes a function "splt" that splits a non-empty list and returns a shorter list as second component (to ensure termination).
.... if we're in the business of proposing generalised search and replace I'd like to propose this one:
http://haskell.org/pipermail/haskell-cafe/2007-July/028032.html
which is along the general lines above but slightly more general.
It's more special in the sense that the result list cannot be "[[a]]" as required for all the above functions except replace.
When I made that posting in 2007 I was hoping for name suggestions. In the absence of anythign better I suggest 'Data.List.transform' or the more whimsical 'Data.List.transmogrify'.
I would also suggest a convenience function 'Data.List.replace' defined from it in the obvious way.
I am also in agreement with 'groupsOf' (which I sometimes called 'chunksOf' but I like both names) proposed by Yitzchak.
Will all that in mind I oppose this proposal, because whilst I fully support filling in some gaps in Data.List I don't think these are the best primitives.
Jules

Dear Christian, et al. Thanks for the summary, Christian. I've given some detailed comments below, but I'll give the gist here. The ticket has indeed moved on quite a bit. Some more expressive functions were proposed that weren't part of the ticket, but that maybe should have been. Some of the originally proposed functions can be expressed easily in these more expressive ones and, therefore, may not be wanted inclusions any more. I suggest we get everyone to +1 or -1 on the following list of possible new inclusions (where the slash-separated list of names all represent the same function - for +1s also indicate name preference): - takeRec / splitAts / groupsOf / segmentsOf :: Int -> [a] -> [[a]] - genericTakeRec / genericSplitAts / genericGroupsOf / genericSegmentsOf :: Integral i => i -> [a] -> [[a]] - spanRec / spans :: (a -> Bool) -> [a] -> [[a]] - breakRec / breaks :: (a -> Bool) -> [a] -> [[a]] - runs :: (a -> a -> Bool) -> [a] -> [[a]] - run :: (a -> a -> Bool) -> [a] -> ([a],[a]) - replace :: Eq a => [a] -> [a] -> [a] -> [a] - replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] The implementations of the chosen functions should, in my mind, be based on profiling results. As an open procedural question: can a proposal track ticket be obsolidated by a new ticket? What is the common procedure for revising a proposal? Regards, Philip On Tue, 2009-11-24 at 10:23 +0100, Christian Maeder wrote:
Ok, lets try to get back to the proposal.
Good idea. I think there is general consensus that *something* along these lines should be added, but we have to agree on what. Clearly, the original proposal has undergone such revision that we might want to obsolidate it. Is there a replacement procedure for Trac proposals?
1. We want something like takeRec being named splitAts or groupsOf (groupsOf is too similar to the existing groupsBy)
Although I liked groupsOf, I see your point. Suggestion for alternative: segmentsOf
2. genericTakeRec is just a variant of takeRec based on genericSplitAt rather than splitAt (or genericTake, genericDrop instead of take, drop)
Correct, but whatever it's going to be called, a genericX variant seems reasonable.
3. spanRec changed to a mutual recursive implementation for spans and breaks (in the ticket) that is not supported much. Rather breaks was more discussed in this thread as a splitting function (that was discussed years before under splitBy or splitOn without any agreement.)
Agreement seems to be about "breaks p = spans (not . p)" (or vice versa)
Furthermore, proposal for runs (4.) and replace (5.) came up in this thread, that are not part of the ticket.
You're absolutely right about this and I feel it would be better to fix this. Hence: Is there a replacement procedure for a proposal ticket?
4. I find "runs" useful in the sense proposed by Philip with type
runs :: (a -> a -> Bool) -> [a] -> [[a]]
runs (<) [1,2,3,4,3,4,5] [[1,2,3,4],[3,4,5]]
(there's no proposal to rename groupsBy)
5. The type of my replace function was:
replace :: Eq a => [a] -> a -> [a] -> [a]
and a (reasonable) alternative would be to replace a sublist by another sublist and not by a single element.
I actually thought your replaceBy was very nice, especially because it allows for the expression of all the other functions. Most significantly, the '[b]' result type really works for me.
Which of the above functions (1. - 4.) should be part of the proposal?
Methinks 1-5, no?
How should these functions be implemented?
I only made a proposal how they could be implemented using replaceBy (below), but direct recursive definitions may be more appropriate.
I.e. unlines and unwords are also defined with explicit recursion although alternative definitions are there (based on concatMap and foldr1)
I think implementation choices should depend more than anything on performance. As I remarked somewhere else in this thread, performance might very well be a sliding argument over different compiler versions. I would propose we first vote on the functions we want in there (it seems that also determines some of the implementation choices available) and then to just profile the alternative implementations.

Philip K.F. Hölzenspies schrieb:
Dear Christian, et al.
Thanks for the summary, Christian. I've given some detailed comments below, but I'll give the gist here.
The ticket has indeed moved on quite a bit. Some more expressive functions were proposed that weren't part of the ticket, but that maybe should have been. Some of the originally proposed functions can be expressed easily in these more expressive ones and, therefore, may not be wanted inclusions any more.
I suggest we get everyone to +1 or -1 on the following list of possible new inclusions (where the slash-separated list of names all represent the same function - for +1s also indicate name preference):
- takeRec / splitAts / groupsOf / segmentsOf :: Int -> [a] -> [[a]] +1
in http://hackage.haskell.org/package/split such a function is called "chunk" and "splitEvery". My preference would be "chunks", but "splitAts", "splits", or "segmentsOf" is fine, too.
- genericTakeRec / genericSplitAts / genericGroupsOf / genericSegmentsOf :: Integral i => i -> [a] -> [[a]] +1
How should the above functions behave for the corner case of the number being less than 1? I see several options: 1. abort (my preference) 2. return the empty list 3. return the singleton list of the input (non-intuitive) 4. return the infinite list of empty lists
- spanRec / spans :: (a -> Bool) -> [a] -> [[a]] - breakRec / breaks :: (a -> Bool) -> [a] -> [[a]] +1
in http://hackage.haskell.org/package/split there is a function called splitWhen. The main point to clarify is how delimiters (determined by the input predicate for breaks) influence the output list. 1. Should delimiters be part of the output? 2. Should consecutive delimiters produce separate sublists 3. Should empty lists be elements of the result list 4. If yes, should leading or trailing delimiters produce leading or trailing empty list elements.
- runs :: (a -> a -> Bool) -> [a] -> [[a]] +1
maybe under a different name: "runBy"
- run :: (a -> a -> Bool) -> [a] -> ([a],[a]) -1
"runs" is similar to "groupBy", therefore I proposed "runBy" for "runs". For groupBy we have no function that's splits off the first group only, therefore (I think) we don't need one for the first run, too. Furthermore, the relation between "runBy" und "run" would be different from the one between "groupBy" and "group". An alternative would be to use "firstRunBy" for "run" and also add a function "firstGroupBy".
- replace :: Eq a => [a] -> [a] -> [a] -> [a] +1
Here also the corner case needs to be clarified, what should happen, if the empty list should be replaced.
- replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] -1
As a recursion scheme that is comparable to iterate or replicate the name is too special. I also just notice that a more general recursion scheme would be: recurse :: (a -> (b, Maybe a)) -> a -> [b] or the given unfoldr :: (b -> Maybe (a, b)) -> b -> [a] unfoldr could be used directly in a similar way than my replaceBy. In fact: replaceBy splt = unfoldr (\ l -> if null l then Nothing else Just (splt l)) So replaceBy is not really needed!
The implementations of the chosen functions should, in my mind, be based on profiling results.
Yes.
As an open procedural question: can a proposal track ticket be obsolidated by a new ticket? What is the common procedure for revising a proposal?
I actually don't know. But I would recommend to close this ticket and open a new one (or several new ones) if some agreement is achieved (or none without agreement). Cheers Christian
participants (8)
-
Bulat Ziganshin
-
Christian Maeder
-
Ian Lynagh
-
Josef Svenningsson
-
Jules Bean
-
Malcolm Wallace
-
Philip K.F. Hölzenspies
-
Yitzchak Gale