Is this a useful higher-order function, or should I RTFM?

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

On Dec 3, 2004, at 1:28 PM, Steven Huwig wrote:
I am basically a newbie at Haskell, and have been experimenting with it where typically I would use Python. ... 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] 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?
(Bad form to self-reply, I know.) The answer to that question is yes. -- mapGroups :: (a -> Bool) -> ([a] -> [a]) -> [a] -> [a] mapGroups = mapGroups' [] mapGroups' :: [a] -> (a -> Bool) -> ([a] -> [a]) -> [a] -> [a] mapGroups' acc _ _ [] = acc mapGroups' acc p f z@(x:_) | p x = mapGroups' (acc ++ f part1) p f part2 | otherwise = mapGroups' (acc ++ part1') p f part2' where (part1, part2) = span p z (part1', part2') = span (not . p) z mapWords = mapGroups (not . isSpace) initcap :: String -> String initcap (c:cs) = toUpper c:[toLower c' | c' <- cs] main = putStrLn (mapWords initcap "This\nis\t\ta test\n") -- Now I can solicit your remarks yet again :) -- Steven Huwig

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Steven Huwig wrote: [...]
1) Did I miss something in the Prelude or standard library that gives me this functionality, or something close to it?
[...]
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?
Here's another way to get something similar. import Data.Char(isSpace) import Data.List(groupBy) (op `on` f) x y = f x `op` f y wordsAndSpaces = groupBy ((==) `on` isSpace) It has a couple of advantages: laziness, and being reversible by good ol' concat. It's a slight nuisance that you have to use isSpace *again* to get your bearings, if you use wordsAndSpaces in a mapWords function. Regards, Tom

On Dec 6, 2004, at 11:05 PM, Tom Pledger wrote:
import Data.Char(isSpace) import Data.List(groupBy)
(op `on` f) x y = f x `op` f y wordsAndSpaces = groupBy ((==) `on` isSpace)
`on` is a handy little function in this instance. Does it have a technical name? Have you used it elsewhere? -- Steve

Steven Huwig wrote:
On Dec 6, 2004, at 11:05 PM, Tom Pledger wrote:
import Data.Char(isSpace) import Data.List(groupBy)
(op `on` f) x y = f x `op` f y wordsAndSpaces = groupBy ((==) `on` isSpace)
`on` is a handy little function in this instance.
Does it have a technical name?
Perhaps, but I don't know it, and wanted to make the code sound OK when read aloud. :-)
Have you used it elsewhere?
Yes, a few times, mainly as (compare `on` fst), as in: -- Apply to xs the permutation that would stably sort ks unpermute ks xs = map snd (sortBy (compare `on` fst) (zip ks xs)) Regards, Tom
participants (3)
-
Lemmih
-
Steven Huwig
-
Tom Pledger