ANNOUNCE: The Monad.Reader - Issue 6

Dear all, I pleased to announce that the latest issue of The Monad.Reader is now available: http://www.haskell.org/haskellwiki/The_Monad.Reader Issue 6 consists of the following three articles: * Bernie Pope - Getting a Fix from the Right Fold * Dan Piponi - Adventures in Classical-Land * Russell O'Connor - Assembly: Circular Programming with Recursive do The Monad.Reader is a quarterly magazine about all things Haskell. It is less-formal than journal, but somehow more enduring than a wiki- page or blog post. If you'd like to submit something to the next issue of The Monad.Reader, please get in touch. The preliminary deadline for Issue 7 is March 30, 2007. I will send out an official call for copy in the coming weeks. For now, enjoy Issue 6! Wouter This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Wouter Swierstra wrote:
I pleased to announce that the latest issue of The Monad.Reader is now available: [...]
Horray, the long awaited new issue of my favorite breakfast reading is out!
* Bernie Pope - Getting a Fix from the Right Fold [...]
Concerning the strictness of dwBackwards, it suffices to make the pattern match on (ys,xs) irrefutable: dwBackwards predicate = fst . dwPairs predicate dwPairs :: (a -> Bool) -> [a] -> ([a], [a]) dwPairs predicate = foldr combine base where --> combine next ~(ys, xs) | predicate next = (ys, next:xs) | otherwise = (next:xs, next:xs) base = ([], []) Regards, apfelmus

On 31 Jan 2007, at 13:39, apfelmus@quantentunnel.de wrote:
Concerning the strictness of dwBackwards, it suffices to make the pattern match on (ys,xs) irrefutable: <snip>
I probably should have mentioned this in my original announcement, but there's also a discussion page for comments and feedback: http://www.haskell.org/haskellwiki/Talk:The_Monad.Reader All the best, Wouter This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Wouter Swierstra
* Bernie Pope - Getting a Fix from the Right Fold
i ended up with this one: dwBool predicate l = (foldr combine (\_ -> []) l) True where combine e fl beg = if beg && predicate e then fl True else e : fl False higher-order, like solutions 3 & 4, but simpler IMO :p

On 31/01/07, Pixel
i ended up with this one:
dwBool predicate l = (foldr combine (\_ -> []) l) True where combine e fl beg = if beg && predicate e then fl True else e : fl False
Mine was: dw :: (a -> Bool) -> [a] -> [a] dw p = reverse . fst . foldl comb ([],False) where comb (xs,done) x | done = (x:xs, True) | p x = (xs, False) | otherwise = (x:xs, True) Which is the simplest working algorithm I could come up with; sadly it breaks the lazinesss constraint. It was a great article though, seeing fix's definition in terms of foldr was one of those mind-bending moments which makes learning Haskell what it is. -- -David House, dmhouse@gmail.com

dw :: (a -> Bool) -> [a] -> [a] dw p = reverse . fst . foldl comb ([],False) where comb (xs,done) x | done = (x:xs, True) | p x = (xs, False) | otherwise = (x:xs, True)
Which is the simplest working algorithm I could come up with; sadly it breaks the lazinesss constraint.
Speaking of the laziness constraint, the simplest solution to the strictness of dwBackwards (solution 1) would be to use irrefutable pattern matching in the combine function: dwBackwards predicate = fst . foldr combine ([],[]) where -- Note the tilde in the next line... combine x ~(ys,xs) | predicate x = (ys, x:xs) | otherwise = (x:xs, x:xs)

On 31/01/07, David House
dw :: (a -> Bool) -> [a] -> [a] dw p = reverse . fst . foldl comb ([],False) where comb (xs,done) x | done = (x:xs, True) | p x = (xs, False) | otherwise = (x:xs, True)
I forgot to mention: I used foldl because it was neater, but you can easily convert it to use foldr by reversing the list first and swapping the arguments to comb. -- -David House, dmhouse@gmail.com

David House wrote:
It was a great article though, seeing fix's definition in terms of foldr was one of those mind-bending moments which makes learning Haskell what it is.
It's nice to see so many new solutions posted in the cafe. The great thing about Haskell is that it keeps on giving :) Cheers, Bernie.

Pixel wrote:
i ended up with this one:
dwBool predicate l = (foldr combine (\_ -> []) l) True where combine e fl beg = if beg && predicate e then fl True else e : fl False
higher-order, like solutions 3 & 4, but simpler IMO :p
This looks more like solution 1 to me. The only real difference is that you use 'Bool -> a' to keep track of the two intermediate results, where solution 1 uses the isomorphic '(a,a)'. Nice exercise! Kind regards, Arie

Yet another higher order solution: dropWhile' p0 xs = foldr f (const []) xs $ p0 where f y ys p | p y = ys p | otherwise = y : ys (const False) Spencer Janssen
participants (8)
-
apfelmus@quantentunnel.de
-
Arie Peterson
-
Bernie Pope
-
David House
-
Matthew Brecknell
-
Pixel
-
Spencer Janssen
-
Wouter Swierstra