[Haskell-beginners] short function to remove and replace an item

Daniel Fischer daniel.is.fischer at web.de
Wed Apr 1 21:38:40 EDT 2009


Am Donnerstag 02 April 2009 02:45:29 schrieb Michael P Mossey:
> What if I have a list xs, and I want to remove one item and replace it
> with another? The item to remove can be detected by a predicate
> function. The order of the items doesn't matter. How about this:

From the description, I'd rather have expected something like

replaceItem :: (a -> Bool) -> a -> [a] -> [a]
replaceItem p new (x:xs)
	| p x	    = new : xs     -- or new : replaceItem p new xs
	| otherwise = x : replaceItem p new xs
replaceItem _ _ [] = []

which could also be nicely written  as

replaceItem p new xs =
      case break p xs of
        (front,_:back) -> front ++ new : back
        _ -> xs

the multiple replace: map (\x -> if p x then new else x) xs

>
> replaceItem :: (a -> Bool) -> a -> [a] -> [a]
> replaceItem p new xs = new : snd (partition p xs)

This could also be written as

replaceItem p new xs = new : filter (not . p) xs

>
> This will actually replace all items that match the predicate with one
> copy of 'new'. It will also prepend 'new' even if no items match the
> predicate.
>
> For another challenge, can someone explain to me how to write this in
> point-free style?

replaceItem p new xs = new : snd (partition p xs)

rewrite the right hand side as

(new :) . snd . (partition p) $ xs

Now you can drop the last argument (xs)

replaceItem p new = (new :) . snd . partition p

To move new to the end, rewrite the right hand side as

((:) new) . (snd . partition p)
   === (. (snd . partition p)) . (:) $ new

Now you can drop the next parameter, new:

replaceItem p = (. (snd . partition p)) . (:)

To move the predicate p to the end, rewrite the right hand side as

(.) (. (snd . partition p)) (:)
   === flip (.) (:) (. (snd . partition p))
   === flip (.) (:) $ flip (.) (snd . partition p)
   === flip (.) (:) $ flip (.) ((snd .) . partition $ p)
   === flip (.) (:) . flip (.) $ ((snd .) . partition $ p)
   === flip (.) (:) . flip (.) . (snd .) . partition $ p

Now you can drop the last parameter, p:

replaceItem = flip (.) (:) . flip (.) . (.) snd . partition

Prelude Data.List> let replaceItem = flip (.) (:) . flip (.) . (.) snd . partition in 
replaceItem even 7 [1 .. 20]
[7,1,3,5,7,9,11,13,15,17,19]

But please, don't write your code in that style. Getting rid of xs is fine, dropping 
new leads to hard to read code. Removing all arguments is sheer obfuscation.
There's more to writing pointfree code than being able to, one must also know 
when to stop.

>
> Thanks,
> Mike

Cheers,
Daniel




More information about the Beginners mailing list