
Udo Stenzel wrote:
jim burton wrote:
I want to split a string into 5 parts of equal length, with the last fifth padded if necessary, but can't get it right - here's what I've got -
fifths s = unwords.take 5.unfoldr (Just . splitAt l) $ s ++ repeat ' ' where l = (length s + 4) `div` 5
Okay, you win. That's the nicest answer so far, I think. But here are solutions with a different theme altogether. They are based on groupBy, not unfoldr. I really like the new `on` function. module Chunk where import Data.List (on) f g = \x y -> f (g x) (g y) groupByIndex test xs = map (map snd) $ groupBy (test `on` fst) $ zip [0..] xs -- chunk : divide the input string into n chunks of equal length (len), with padding -- chunk1 accepts the number of chunks chunk1 n pad xs = unwords $ take n $ groupByIndex ((==) `on` (`div` len)) $ xs ++ repeat pad where len = (length xs + n - 1) `div` n -- chunk2 accepts the length of each chunk chunk2 len pad xs = unwords $ take n $ groupByIndex ((==) `on` (`div` len)) $ xs ++ repeat pad where n = (length xs + len - 1) `div` len