Removing alternate items from a list

What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]? _________________________________________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. http://www.windowslive.com/campaign/thenewbusy?ocid=PID28326::T:WLMTAGL:ON:W...

maybe this?
map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

i think explicit recursion is quite clean?
f :: [a] -> [a]
f (x:y:zs) = x : f zs
f x = x
On 7 June 2010 19:42, Thomas Hartman
maybe this?
map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
: What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun

or, since you don't need to give a name to the second element of the list:
f :: [a] -> [a]
f (x:_:xs) = x : f xs
f x = x
On 7 June 2010 20:11, Ozgur Akgun
i think explicit recursion is quite clean?
f :: [a] -> [a] f (x:y:zs) = x : f zs f x = x
On 7 June 2010 19:42, Thomas Hartman
wrote: maybe this?
map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
: What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun

f :: [a] -> [a]
f = filter snd $ zip a (cycle [True, False])
On Monday, June 7, 2010, Ozgur Akgun
or, since you don't need to give a name to the second element of the list:
f :: [a] -> [a] f (x:_:xs) = x : f xsf x = x
On 7 June 2010 20:11, Ozgur Akgun
wrote: i think explicit recursion is quite clean?
f :: [a] -> [a]f (x:y:zs) = x : f zs
f x = x
On 7 June 2010 19:42, Thomas Hartman
wrote: maybe this? map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
: What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun

if we add 'a' to the definition of this function, (to make it work), the
type of it turns out to be: [a] -> [(a, Bool)]
you might have forgotten the "map fst $" part.
Best,
On 8 June 2010 14:51, Bill Atkins
f :: [a] -> [a] f = filter snd $ zip a (cycle [True, False])
or, since you don't need to give a name to the second element of the
On Monday, June 7, 2010, Ozgur Akgun
wrote: list: f :: [a] -> [a] f (x:_:xs) = x : f xsf x = x
On 7 June 2010 20:11, Ozgur Akgun
wrote: i think explicit recursion is quite clean?
f :: [a] -> [a]f (x:y:zs) = x : f zs
f x = x
On 7 June 2010 19:42, Thomas Hartman
wrote: maybe this? map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
: What's the cleanest definition for a function f :: [a] -> [a] that takes
a
list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun
-- Ozgur Akgun

Yes, this was an old draft I accidentally sent out.
My post higher up the thread is correct. :)
On Tuesday, June 8, 2010, Ozgur Akgun
if we add 'a' to the definition of this function, (to make it work), the type of it turns out to be: [a] -> [(a, Bool)]
you might have forgotten the "map fst $" part.
Best,
On 8 June 2010 14:51, Bill Atkins
wrote: f :: [a] -> [a] f = filter snd $ zip a (cycle [True, False])
On Monday, June 7, 2010, Ozgur Akgun
wrote: or, since you don't need to give a name to the second element of the list:
f :: [a] -> [a] f (x:_:xs) = x : f xsf x = x
On 7 June 2010 20:11, Ozgur Akgun
wrote: i think explicit recursion is quite clean?
f :: [a] -> [a]f (x:y:zs) = x : f zs
f x = x
On 7 June 2010 19:42, Thomas Hartman
wrote: maybe this? map snd . filter (odd . fst) . zip [1,2..] $ [1,2,3,4,5]
2010/6/6 R J
: What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun
-- Ozgur Akgun

alts :: [a] -> [a] alts xs = map fst . filter snd $ zip xs (cycle [False, True]) Prelude> alts [0, 1..5] [1,3, 5] On Sunday Jun 6, 2010, at 10:46 AM, R J wrote:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Can't forget fix in a game of code golf!
(fix $ \f (x:_: xs) -> x : f xs) [1..] => [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31,33,35,37,39,41,4...
2010/6/8 Yitzchak Gale
R J wrote:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
f = map head . takeWhile (not . null) . iterate (drop 2) . drop 1
Regards, Yitz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Christopher Done wrote:
Can't forget fix in a game of code golf!
(fix $ \f (x:_: xs) -> x : f xs) [1..] => [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31,33,35,37,39,41,4...
Ho, good shot! It only works for infinite lists, though: Prelude> (fix $ \f (x:_: xs) -> x : f xs) [1..10] [1,3,5,7,9*** Exception: <interactive>:1:7-30: Non-exhaustive patterns in lambda Regards, Yitz

It only works for infinite lists, though
you wanted it :)
(fix $ \f xs -> case xs of { (x:_: xs) -> x : f xs; _ -> [] }) [1..10]
= [1,3,5,7,9]
here you go :)
2010/6/8 Yitzchak Gale
Christopher Done wrote:
Can't forget fix in a game of code golf!
(fix $ \f (x:_: xs) -> x : f xs) [1..] => [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31,33,35,37,39,41,4...
Ho, good shot! It only works for infinite lists, though:
Prelude> (fix $ \f (x:_: xs) -> x : f xs) [1..10] [1,3,5,7,9*** Exception: <interactive>:1:7-30: Non-exhaustive patterns in lambda
Regards, Yitz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun

And for a few more lines of codes, you get a more flexible solution:
data Consume = Take | Skip
consumeBy :: [Consume] -> [a] -> [a]
consumeBy [] _ = []
consumeBy _ [] = []
consumeBy (tOrS:takesAndSkips) (x:xs) = case tOrS of
Take -> x : consumeBy takesAndSkips xs
Skip -> consumeBy
takesAndSkips xs
*Main> consumeBy (cycle [Take,Take,Skip]) [1,2,3,4,5,6]
[1,2,4,5]
*Main> consumeBy (cycle [Take,Take,Take,Skip]) [1,2,3,4,5,6]
[1,2,3,5,6]
-deech
On 6/8/10, Christopher Done
Can't forget fix in a game of code golf!
(fix $ \f (x:_: xs) -> x : f xs) [1..] => [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31,33,35,37,39,41,4...
2010/6/8 Yitzchak Gale
: R J wrote:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
f = map head . takeWhile (not . null) . iterate (drop 2) . drop 1
Regards, Yitz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello The regular list functionals - map, zip, foldl, foldr, filter, etc. - all process the input list at "speed 1" - i.e. one element at a time. As Ozgur Akgun has shown - consuming the list at "speed 2" gives a very pleasant implementation - algorithmically: "consume at speed 2, produce the new list with the first element of the two and drop the second". Trying to code an algorithm at "speed 1" with the list functionals presents a significant hurdle towards clarity of exposition... Best wishes Stephen

El dom, 06-06-2010 a las 14:46 +0000, R J escribió:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
adding another suggestion: import Data.Either(rights) f = rights . zipWith ($) (cycle [Left,Right]) Jürgen

On 8 June 2010 15:13, Jürgen Doser
El dom, 06-06-2010 a las 14:46 +0000, R J escribió:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
adding another suggestion:
import Data.Either(rights)
f = rights . zipWith ($) (cycle [Left,Right])
Ohhh. Nice.

So out of curiosity i took the definitions given in this thread, and tried to run timing-tests. Here's what I ran:
ghc -prof -auto-all -o Test Test.h Test +RTS -p and then looked in the Test.prof file.
All tests I ran from 3 to 10 times (depending on how sure I wanted to be), so the results are not entirely exact. (I copied the "average" result to the source-file as comments above every function.) As the function doing (x:_:rest) pattern-matching was the fastest I extended the idea from that to (x1:_:x2: ... x10:_:rest), but skipping from 5 to 10, where all steps showed a small increase in performance. So a question: when increasing the pattern matched, is it somekind of way of inlining the matchings, and if so, is there some way of just saying that to the compiler how many recursions you want to inline together to increase speed? Any comments? (besides -O2 ;-) -- I remembered it too late and didn't want to restart... At least for the last two functions it showed a similar difference in seconds as with no -O2) Markus Läll

Forgot the file -- here it is:
module Main where
import Data.Either (rights)
import Data.Function (fix)
test f = putStr $ show $ last $ f $ replicate 10000000 (1 :: Int)
main = test matchPattern4
-- 1. zipNums
-- 2. matchPattern
-- 3. zipBoolCycle
-- 4. iterDrop
-- 5. zipBoolCycle2
-- 6. consume
-- 7. eitherr
-- 8. golf
-- 9. matchPattern2
-- 10. matchPattern3
-- 11. matchPattern4
-- 12. matchPattern5
-- 13. matchPattern10
-- 1. total time = 13.72 secs (686 ticks @ 20 ms)
-- total alloc = 1,840,007,000 bytes (excludes profiling overheads)
zipNums = map snd . filter (odd . fst) . zip [1,2..]
-- 2. total time = 1.82 secs (91 ticks @ 20 ms)
-- total alloc = 400,006,752 bytes (excludes profiling overheads)
matchPattern (x:_:zs) = x : matchPattern zs
matchPattern x = x
-- 3. total time = 4.46 secs (223 ticks @ 20 ms)
-- total alloc = 1,040,006,904 bytes (excludes profiling overhea
zipBoolCycle xs = map fst . filter snd $ zip xs (cycle [False, True])
-- 4 total time = 5.20 secs (260 ticks @ 20 ms)
-- total alloc = 940,006,916 bytes (excludes profiling overheads)
iterDrop = map head . takeWhile (not . null) . iterate (drop 2) . drop 1
-- 5 total time = 3.68 secs (184 ticks @ 20 ms)
-- total alloc = 820,006,872 bytes (excludes profiling overheads)
zipBoolCycle2 x = [y | (True, y) <- zip (cycle [False, True]) x]
-- 6. total time = 2.46 secs (123 ticks @ 20 ms)
-- total alloc = 420,006,860 bytes (excludes profiling overheads)
data Consume = Take | Skip
consumeBy :: [Consume] -> [a] -> [a]
consumeBy [] _ = []
consumeBy _ [] = []
consumeBy (tOrS:takesAndSkips) (x:xs) =
case tOrS of Take -> x : consumeBy takesAndSkips xs
Skip -> consumeBy takesAndSkips xs
consume = consumeBy $ cycle [Take, Skip]
-- 7. total time = 4.10 secs (205 ticks @ 20 ms)
-- total alloc = 1,000,006,884 bytes (excludes profiling overheads)
eitherr = rights . zipWith ($) (cycle [Left,Right])
-- 8. total time = 2.08 secs (104 ticks @ 20 ms)
-- total alloc = 420,006,784 bytes (excludes profiling overheads)
golf = (fix $ \f xs -> case xs of { (x:_: xs) -> x : f xs; _ -> [] })
-- 9. total time = 1.68 secs (84 ticks @ 20 ms)
-- total alloc = 370,006,752 bytes (excludes profiling overheads)
matchPattern2 (a:_:c:_:rest) = a : c : matchPattern2 rest
matchPattern2 (a:_:rest) = a : rest
matchPattern2 (rest) = rest
-- 10. total time = 1.58 secs (79 ticks @ 20 ms)
-- total alloc = 360,006,744 bytes (excludes profiling overheads)
matchPattern3 (a:_:c:_:e:_: rest) = a : c : e : matchPattern3 rest
matchPattern3 (a:_:c:_:rest) = a : c : rest
matchPattern3 (a:_:rest) = a : rest
matchPattern3 (rest) = rest
-- 11. total time = 1.56 secs (78 ticks @ 20 ms)
-- total alloc = 355,006,752 bytes (excludes profiling overheads)
matchPattern4 (a:_:c:_:e:_:g:_:rest) = a : c : e : g : matchPattern4 rest
matchPattern4 (a:_:c:_:e:_: rest) = a : c : e : rest
matchPattern4 (a:_:c:_:rest) = a : c : rest
matchPattern4 (a:_:rest) = a : rest
matchPattern4 (rest) = rest
-- 12. total time = 1.52 secs (76 ticks @ 20 ms)
-- total alloc = 352,006,752 bytes (excludes profiling overheads)
matchPattern5 (a:_:c:_:e:_:g:_:i:_:rest) = a : c : e : g : i :
matchPattern5 rest
matchPattern5 (a:_:c:_:e:_:g:_:rest) = a : c : e : g : rest
matchPattern5 (a:_:c:_:e:_: rest) = a : c : e : rest
matchPattern5 (a:_:c:_:rest) = a : c : rest
matchPattern5 (a:_:rest) = a : rest
matchPattern5 (rest) = rest
-- 13. total time = 1.48 secs (74 ticks @ 20 ms)
-- total alloc = 346,006,752 bytes (excludes profiling overheads)
matchPattern10 (a:_:c:_:e:_:g:_:i:_:k:_:m:_:o:_:q:_:s:_:rest) =
a:c:e:g:i:k:m:o:q:s: matchPattern10 rest
matchPattern10 (a:_:c:_:e:_:g:_:i:_:k:_:m:_:o:_:q:_:rest) =
a:c:e:g:i:k:m:o:q:rest
matchPattern10 (a:_:c:_:e:_:g:_:i:_:k:_:m:_:o:_:rest) =
a:c:e:g:i:k:m:o:rest
matchPattern10 (a:_:c:_:e:_:g:_:i:_:k:_:m:_:rest) =
a:c:e:g:i:k:m:rest
matchPattern10 (a:_:c:_:e:_:g:_:i:_:k:_:rest) = a:c:e:g:i:k:rest
matchPattern10 (a:_:c:_:e:_:g:_:i:_:rest) = a:c:e:g:i:rest
matchPattern10 (a:_:c:_:e:_:g:_:rest) = a:c:e:g:rest
matchPattern10 (a:_:c:_:e:_: rest) = a:c:e:rest
matchPattern10 (a:_:c:_:rest) = a:c:rest
matchPattern10 (a:_:rest) = a:rest
matchPattern10 (rest) = rest
On Wed, Jun 9, 2010 at 11:47 PM, Markus Läll
So out of curiosity i took the definitions given in this thread, and tried to run timing-tests. Here's what I ran:
ghc -prof -auto-all -o Test Test.h Test +RTS -p and then looked in the Test.prof file.
All tests I ran from 3 to 10 times (depending on how sure I wanted to be), so the results are not entirely exact. (I copied the "average" result to the source-file as comments above every function.)
As the function doing (x:_:rest) pattern-matching was the fastest I extended the idea from that to (x1:_:x2: ... x10:_:rest), but skipping from 5 to 10, where all steps showed a small increase in performance.
So a question: when increasing the pattern matched, is it somekind of way of inlining the matchings, and if so, is there some way of just saying that to the compiler how many recursions you want to inline together to increase speed?
Any comments? (besides -O2 ;-) -- I remembered it too late and didn't want to restart... At least for the last two functions it showed a similar difference in seconds as with no -O2)
Markus Läll

Markus Läll wrote:
So out of curiosity i took the definitions given in this thread, and tried to run timing-tests.
Nice!
Any comments? (besides -O2 ;-) -- I remembered it too late and didn't want to restart...
Oh, could you please run that again with -O2? My entry dearly depends on it :) Thanks, Yitz

On Wed, Jun 09, 2010 at 11:47:32PM +0300, Markus Läll wrote:
As the function doing (x:_:rest) pattern-matching was the fastest I extended the idea from that to (x1:_:x2: ... x10:_:rest), but skipping from 5 to 10, where all steps showed a small increase in performance.
So a question: when increasing the pattern matched, is it somekind of way of inlining the matchings, and if so, is there some way of just saying that to the compiler how many recursions you want to inline together to increase speed?
What you are describing is somewhat akin to a loop unrolling optimization, which is a fairly common thing for a compiler to do. However, as you described it, it is not actually a valid optimization in haskell. compare take 2 (matchPattern5 (1:2:3:4:undefined)) => undefined take 2 (matchPattern (1:2:3:4:undefined)) => [1,3] John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

OK, here's mine: f as = [ x | (True,x) <- zip (cycle [True, False]) as ] -md begin R J quotation:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
_________________________________________________________________ The New Busy is not the old busy. Search, chat and e-mail from your inbox. http://www.windowslive.com/campaign/thenewbusy?ocid=PID28326::T:WLMTAGL:ON:W...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Or, when lists had a decent eliminator defined in the Prelude (just like maybe for Maybe and either for Either): list :: b -> (a -> [a] -> b) -> [a] -> b list d _ [] = d list _ f (x:xs) = f x xs fromList = list [] we could write the alternate function like this: alt :: [a] -> [a] alt = list [] $ \a -> (a:) . list [] (const alt) -- Sebastiaan On Jun 6, 2010, at 4:46 PM, R J wrote:
What's the cleanest definition for a function f :: [a] -> [a] that takes a list and returns the same list, with alternate items removed? e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?
The New Busy is not the old busy. Search, chat and e-mail from your inbox. Get started._______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Yep, the test is done by a rookie. If I get more time, I'll try to look into testing a little more, and redo the timing (if anyone doesn't do it firs) -- using optimizations, more runs per function and the criterion package.
participants (14)
-
aditya siram
-
Alexey Levan
-
Bill Atkins
-
Christopher Done
-
John Meacham
-
Jürgen Doser
-
Markus Läll
-
Mike Dillon
-
Ozgur Akgun
-
R J
-
Sebastiaan Visser
-
Stephen Tetley
-
Thomas Hartman
-
Yitzchak Gale