split string into n parts

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 :: String -> String fifths s = fifths' "" 0 s where l = (length s) `div` 5 fifths' xs c [] = xs ++ (replicate (l-c) 'X') fifths' xs c (y:ys) = if c == l then fifths' (xs++[' ',y]) 0 ys else fifths' (xs++[y]) (c+1) ys
which, apart from surely being uglier than need be, doesn't work: *Main> fifths "IDOLIKETOBEBESIDETHESEASIDE" "IDOLI KETOBE BESIDE THESEA SIDEXX" *Main> fifths "12345" "1 23 45" Any thoughts? Thanks! This isn't homework BTW, I'm having a go at the ruby quiz puzzles in haskell, which seems to be a nice way to learn. -- View this message in context: http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6960346 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello jim, Monday, October 23, 2006, 11:29:07 PM, you 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 :: String -> String fifths s = unwords [a1,a2,a3,a4,a5] where l = (length s) `div` 5 s0 = s++" " (a1,s1) = splitAt l s0 (a2,s2) = splitAt l s1 ...
you can also use the following func: splitByLen (len:lens) list = (x:splitByLens lens xs) where (x,xs) = splitAt len list splitByLen [] [] = [] -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

jim burton
I want to split a string into 5 parts of equal length, with the last fifth padded if necessary (snip) *Main> fifths "12345" "1 23 45"
What's the correct answer for fifths "123456"? I can't figure out how to meet both your constraints. Is "12 34 56 XX XX" permitted (padding before fifth as well)? -- Mark

jim burton
*Main> fifths "IDOLIKETOBEBESIDETHESEASIDE" "IDOLI KETOBE BESIDE THESEA SIDEXX" *Main> fifths "12345" "1 23 45" (snip)
FWIW this unholy thing works for me, fifths :: String -> String fifths = splitIntoN 5 splitIntoN :: Int -> String -> String splitIntoN n string = let stringToSplit = string ++ replicate (n-1) 'X' in unwords (map fst (take n (tail (iterate (splitAt (div (length stringToSplit) n) . snd) (undefined, stringToSplit))))) Admittedly, a 'let' might be nice to name some intermediate computations. -- Mark

Mark T.B. Carroll-2 wrote:
FWIW this unholy thing works for me,
fifths :: String -> String
fifths = splitIntoN 5
[snip]
Thanks Mark. -- View this message in context: http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6961461 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10/23/06, jim burton
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
I got this: fifths :: String -> String fifths xs = let len = (length xs + 4) `div` 5 padded = take (len * 5) (xs ++ " ") in unwords $ nth len padded where nth _ [] = [] nth n xs = (take n xs) : (nth n $ drop n xs)
*Main> fifths "IDOLIKETOBEBESIDETHESEASIDE" "IDOLI KETOBE BESIDE THESEA SIDEXX" *Main> fifths "12345" "1 23 45"
This gives the following results: "IDOLIK ETOBEB ESIDET HESEAS IDE " and "1 2 3 4 5" But it also gives this result, which may or may not be correct for your problem: *Main> fifths "123456" "12 34 56 " -- Rich AIM : rnezzy ICQ : 174908475

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 Of course no Haskeller in his right mind would carelessly apply the final 'unwords' unless this was for immediate output. Udo. -- The Second Law of Thermodynamics: If you think things are in a mess now, just wait! -- Jim Warner

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
participants (6)
-
Bulat Ziganshin
-
Clifford Beshers
-
jim burton
-
mark@ixod.org
-
Rich Neswold
-
Udo Stenzel