
I would like to propose the following function for inclusion in Data.List chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as It's commonly occuring recursion pattern. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list. The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases. Some examples ------------- -- From Data.List group :: (Eq a) => [a] -> [[a]] group = chop (\ xs@(x:_) -> span (==x) xs) -- From Data.List words :: String -> [String] words = filter (not . null) . chop (span (not . isSpace) . dropWhile isSpace) -- From Data.List lines :: String -> [String] lines = chop ((id *** dropNL) . span (/= '\n')) where dropNL ('\n':s) = s; dropNL s = s -- From Data.List tails :: [a] -> [[a]] tails = (++ [[]]) . chop (\ xs@(_:xs') -> (xs, xs')) -- From Data.List map f = chop (\ (x:xs) -> (f x, xs)) -- Split a list into a list of list with length n. splitEveryN n = chop (splitAt n) -- Simple Haskell tokenizer tokenize = chop (head . lex) History ------- I first encountered this function around 1981 when I was talking to Sören Holmström about this recursion pattern and he said that he had also observed it and he called the function chopList. Ever since then I've used chopList a lot, but unfortunately I always have to make my own definition of this common function.

Surely you mean this signature? chop :: ([a] -> (b, [a])) -> [a] -> [b] On 13 Dec 2010, at 17:17, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as

Yes, of course I did. That's what I get for typing instead of using
copy&paste. :)
On Mon, Dec 13, 2010 at 5:36 PM, Malcolm Wallace
Surely you mean this signature?
chop :: ([a] -> (b, [a])) -> [a] -> [b]
On 13 Dec 2010, at 17:17, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as

On 12/13/10 12:17 PM, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: ([a] -> (b, [a])) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
It's commonly occuring recursion pattern. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list.
The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases.
It's also deeply related to iteratees (for the obvious enumerator of a list). The major difference is that iteratees enforce that the consuming function must return a tail of the input stream, whereas this function doesn't require that at all (for both good and ill). The name "chop" seems a bit strange to me, but other than that it's a nice function. -- Live well, ~wren

I don't really care if the function is called chop or not.
But in many cases it is used to chop a list into smaller pieces.
On Tue, Dec 14, 2010 at 12:00 AM, wren ng thornton
On 12/13/10 12:17 PM, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: ([a] -> (b, [a])) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
It's commonly occuring recursion pattern. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list.
The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases.
It's also deeply related to iteratees (for the obvious enumerator of a list). The major difference is that iteratees enforce that the consuming function must return a tail of the input stream, whereas this function doesn't require that at all (for both good and ill).
The name "chop" seems a bit strange to me, but other than that it's a nice function.
-- Live well, ~wren
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I seem to have this function as "replaceBy": 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) replaceBy :: ([a] -> (b, [a])) -> [a] -> [b] replaceBy splt = unfoldr (\ l -> if null l then Nothing else Just (splt l)) Cheers Christian Am 13.12.2010 18:17, schrieb Lennart Augustsson:
I would like to propose the following function for inclusion in Data.List
chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
It's commonly occuring recursion pattern. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list.
The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases.
Some examples -------------
-- From Data.List group :: (Eq a) => [a] -> [[a]] group = chop (\ xs@(x:_) -> span (==x) xs)
-- From Data.List words :: String -> [String] words = filter (not . null) . chop (span (not . isSpace) . dropWhile isSpace)
-- From Data.List lines :: String -> [String] lines = chop ((id *** dropNL) . span (/= '\n')) where dropNL ('\n':s) = s; dropNL s = s
-- From Data.List tails :: [a] -> [[a]] tails = (++ [[]]) . chop (\ xs@(_:xs') -> (xs, xs'))
-- From Data.List map f = chop (\ (x:xs) -> (f x, xs))
-- Split a list into a list of list with length n. splitEveryN n = chop (splitAt n)
-- Simple Haskell tokenizer tokenize = chop (head . lex)
History -------
I first encountered this function around 1981 when I was talking to Sören Holmström about this recursion pattern and he said that he had also observed it and he called the function chopList. Ever since then I've used chopList a lot, but unfortunately I always have to make my own definition of this common function.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, 13 Dec 2010, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
It's commonly occuring recursion pattern. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list.
The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases.
Is the difference between 'unfoldr' and 'chop' just the Maybe result type of f?
I first encountered this function around 1981 when I was talking to S?ren Holmstr?m about this recursion pattern and he said that he had also observed it and he called the function chopList. Ever since then I've used chopList a lot, but unfortunately I always have to make my own definition of this common function.
To work around this problem I have written utility-ht for the basic functions that I need all the time.

Henning,
I would like to propose the following function for inclusion in Data.List chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
Is the difference between 'unfoldr' and 'chop' just the Maybe result type of f?
Yes. chop f = unfoldr g where g [] = Nothing g as = Just (f as) Cheers, Stefan

Yes, chop can be easily written in terms of unfoldr. But the chop function fits better with other existing list functions, like I tried to illustrate with my examples. -- Lennart On Tue, Dec 14, 2010 at 10:40 AM, Stefan Holdermans < stefan@vectorfabrics.com> wrote:
Henning,
I would like to propose the following function for inclusion in Data.List chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
Is the difference between 'unfoldr' and 'chop' just the Maybe result type of f?
Yes.
chop f = unfoldr g where g [] = Nothing g as = Just (f as)
Cheers,
Stefan

On 14 December 2010 15:38, Lennart Augustsson
Yes, chop can be easily written in terms of unfoldr. But the chop function fits better with other existing list functions, like I tried to illustrate with my examples.
I'd expect the primitive definition of chop to be more efficient as well - as there is no intermediate Maybe type. chop - seems a nice function. I'd like to see it in Data.List. Best wishes Stephen

+1 for the inclusion of chop.
The unfoldr relationship is a good thing, because it gives an insight into
when you can do 'chop fusion' by leaning on the unfoldr/destroy rules. ;)
If we actually used unfoldr/destroy fusion, I'd probably advocate for
defining chop in terms of unfoldr as a consequence, to facilitate rewriting,
but noting the relationship at least provides a nice way to handle it for
the stream fusion folks.
-Edward
On Tue, Dec 14, 2010 at 10:38 AM, Lennart Augustsson wrote: Yes, chop can be easily written in terms of unfoldr. But the chop function
fits better with other existing list functions, like I tried to illustrate
with my examples. -- Lennart On Tue, Dec 14, 2010 at 10:40 AM, Stefan Holdermans <
stefan@vectorfabrics.com> wrote: Henning, I would like to propose the following function for inclusion in
Data.List
chop :: (a -> (b, [a]) -> [a] -> [b]
chop _ [] = []
chop f as = b : chop f as'
where (b, as') = f as Is the difference between 'unfoldr' and 'chop' just the Maybe result
type of f? Yes. chop f = unfoldr g
where
g [] = Nothing
g as = Just (f as) Cheers, Stefan _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries

Lennart Augustsson wrote:
chop.. The function is clearly related to unfoldr, but I find it more convenient to use in a lot of cases.
Henning Thielemann wrote:
Is the difference between 'unfoldr' and 'chop' just the Maybe result type of f?
No. unfoldr is slightly more general in that it allows the unfolding to continue on null input. chop is more efficient in the common case that the unfolding stops on null input. Regards, Yitz

Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List chop...
There have been a number of proposals to add functions of this sort to Data.List. Notably, there have been proposals to add some or all of the functions of Data.List.Split (from Brent Yorgey's split package), by those names and by other names, and other related functions. I don't remember all of those proposals, nor do I remember which were accepted and implemented. I'll also note that John Cage has proposed adding a similar function, or perhaps even this exact function, on several occasions. Again, I don't remember the details. Perhaps this is one of the simplest and most general proposals. In fact, in retrospect it might have been better to leave out much of the bloat in Data.List and instead to provide good documentation about various usages of this function. Regards, Yitz

On Tue, Dec 14, 2010 at 12:57:19PM +0200, Yitzchak Gale wrote:
I'll also note that John Cage has proposed adding a similar function, or perhaps even this exact function, on several occasions. Again, I don't remember the details.
Ah yes, you must be referring to his seminal work "Imaginary Landscape No. 17 for Piano, 12 Radios, and Haskell Library Proposal". -Brent

On Mon, Dec 13, 2010 at 05:17:43PM +0000, Lennart Augustsson wrote:
I would like to propose the following function for inclusion in Data.List
chop :: (a -> (b, [a]) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
I've just uploaded a new version of the 'split' package which exports chop. If it does get added to Data.List (of which I'm in favor) I'll remove it from split. -Brent

chop :: ([a] -> (b, [a])) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
Let's compare with an existing similar function, unfoldr. (This is a somewhat academic exploration.) unfoldr :: (c -> Maybe (d, c)) -> c -> [d] c=[a],d=b: ([a] -> Maybe (b, [a])) -> [a] -> [b] chop :: ([a] -> (b, [a])) -> [a] -> [b] In unfoldr, termination is signalled after 'f' and before a value is emitted. In unfoldr, termination is signalled before 'f' by an empty list, even though the list is passed intact to 'f'. That seems peculiar. But it's what we want. 'f' in 'chop' is usually a function that picks an 'n' somehow and yields (g (take n as), drop n as) for f's corresponding 'g', but does it efficiently. Clearly this is boring for an empty list, as (g [], []) would be a repeating constant forever under these conditions. 'f' *can* be different though. It can take into account more of the list than is consumed (e.g. tokenizing "this+that" needs to look at the + before returning "this"): that's pretty common. I wonder if there are any common examples where the returned list /= (drop n as) for some n, though. -Isaac

(+1) for chop - it looks useful, and simple. I can see quite a few
places where I've wanted something similar.
Thanks, Neil
On Wed, Dec 15, 2010 at 2:57 AM, Isaac Dupree
chop :: ([a] -> (b, [a])) -> [a] -> [b] chop _ [] = [] chop f as = b : chop f as' where (b, as') = f as
Let's compare with an existing similar function, unfoldr. (This is a somewhat academic exploration.)
unfoldr :: (c -> Maybe (d, c)) -> c -> [d] c=[a],d=b: ([a] -> Maybe (b, [a])) -> [a] -> [b]
chop :: ([a] -> (b, [a])) -> [a] -> [b]
In unfoldr, termination is signalled after 'f' and before a value is emitted. In unfoldr, termination is signalled before 'f' by an empty list, even though the list is passed intact to 'f'.
That seems peculiar. But it's what we want. 'f' in 'chop' is usually a function that picks an 'n' somehow and yields (g (take n as), drop n as) for f's corresponding 'g', but does it efficiently. Clearly this is boring for an empty list, as (g [], []) would be a repeating constant forever under these conditions. 'f' *can* be different though. It can take into account more of the list than is consumed (e.g. tokenizing "this+that" needs to look at the + before returning "this"): that's pretty common. I wonder if there are any common examples where the returned list /= (drop n as) for some n, though.
-Isaac
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (12)
-
Brent Yorgey
-
Christian Maeder
-
Edward Kmett
-
Henning Thielemann
-
Isaac Dupree
-
Lennart Augustsson
-
Malcolm Wallace
-
Neil Mitchell
-
Stefan Holdermans
-
Stephen Tetley
-
wren ng thornton
-
Yitzchak Gale