[Haskell-cafe] Is this a useful higher-order function, or should I RTFM?

Lemmih lemmih at gmail.com
Fri Dec 3 14:11:38 EST 2004


Hey Steven,

I find this implementation more intuitive:

import Data.Char

mapWords :: (String -> String) -> String -> String
mapWords fn [] = []
mapWords fn string@(c:cs)
    | isSpace c = c:mapWords fn cs
    | otherwise = fn word ++ mapWords fn rest
    where (word,rest) = break isSpace string

capitalize :: String -> String
capitalize (c:cs) = toUpper c:map toLower cs

main = putStrLn . mapWords capitalize $ teststr

Friendly,
  Lemmih

On Fri, 3 Dec 2004 13:28:18 -0500, Steven Huwig <shuwig at columbus.rr.com> wrote:
> I am basically a newbie at Haskell, and have been experimenting with
> it where typically I would use Python.  One source of frustration I
> had with the standard library is that "words . unwords" is not an
> identity function.  I would like to perform per-word transformations
> and predicates while preserving whitespace.  So I implemented
> wordsAndSpaces and unwordsAndSpaces, which I believe to be a decent
> way to get that kind of behavior.  In working on this problem, I
> realized that I was looking for a pair of higher-order functions. My
> code and an example of usage is below:
> 
> --
> 
> unravel :: (a -> Bool) -> [a] -> ([[a]], [[a]], Int)
> unravel _ [] = ([], [], 0)
> unravel p xs = unravel' ([],[], if p (head xs) then 0 else 1) p xs
> 
> unravel' :: ([[a]], [[a]], Int) -> (a-> Bool) -> [a] -> ([[a]], [[a]],
> Int)
> unravel' (sheep, goats, pos) _ [] = (reverse sheep, reverse goats, pos)
> unravel' acc@(sheep, goats, pos) p rest@(x:xs)
>         | p x = unravel' addSheep p (dropWhile p xs)
>         | otherwise = unravel' addGoat p (dropWhile (not . p) xs)
>         where addSheep = ((takeWhile p rest):sheep, goats, pos)
>               addGoat = (sheep, (takeWhile (not . p) rest):goats, pos)
> 
> ravel :: [a] -> ([[a]], [[a]], Int) -> [a]
> ravel zero (sheep, goats, pos)
>      | length sheep > length goats =
>          concat (zipWith (++) sheep (goats ++ repeat zero))
>      | length sheep < length goats =
>          concat (zipWith (++) goats (sheep ++ repeat zero))
>      | pos == 0 = concat (zipWith (++) sheep goats)
>      | otherwise = concat (zipWith (++) goats sheep)
> 
> initcap :: String -> String
> initcap (c:cs) = toUpper c:[toLower c' | c' <- cs]
> 
> wordsAndSpaces = unravel (not . isSpace)
> unwordsAndSpaces = ravel ""
> 
> teststr = "This is a test\n A very\t\t good\ntest"
> 
> main = (putStrLn . unwordsAndSpaces) (map initcap words, spaces, pos)
>      where (words, spaces, pos) = wordsAndSpaces teststr
> 
> --
> 
> So unravel takes a predicate and a list, and returns a tuple of two
> lists -- the first is a list of lists of consecutive elements where
> predicate is true, and the second where they are false. Its opposite
> ravel takes a zero element -- to pad out fenceposts -- and the output of
> unravel, and returns the lists all concatenated together.
> 
> I have several questions about this:
> 
> 1) Did I miss something in the Prelude or standard library that gives
>     me this functionality, or something close to it?
> 
> 2) Do unravel and ravel have any other practical uses on their own?
>     Looking at it, I think they could be used in a single function
>     of type
>         f :: (a->Bool) -> ([a] -> [a]) -> [a] -> [a]
>     that would encapsulate both. E.g.
>         mapWords = f (not . isSpace)
>         main =  putStrLn (mapWords initcap "lots  \tof\nwhitespace")
> 
>     (syntax not checked for sanity)
>     Can one get that function out of the Prelude in an easier manner than
>     above? Is there a simpler way to get that functionality besides
>     composing ravel and unravel with a map in between?
> 
> 3) The 3-tuple output of unravel looks ugly to me, but I can't think
>     of an alternative. For the case where there is an equal number of
>     p-groups and not-p-groups, we need to know which side to start the
>     zipWith. Does anyone have a better way?
> 
> Any comments and criticism are welcome.
> 
> -- Steven Huwig
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list