[Haskell-cafe] Unwrapping long lines in text files

Ronald Guida oddron at gmail.com
Sat Aug 14 12:59:10 EDT 2010


On Sat, Aug 14, 2010 at 12:33 PM, Bill Atkins <watkins at alum.rpi.edu> wrote:
> Try this one (http://gist.github.com/524460)

I noticed that Bill's solution doesn't seem to work if the input text
is infinite.  I found a different solution, which avoids the use of
reverse, and will work even if the input is infinite, as long as the
words themselves are finite in length.

(http://hpaste.org/fastcgi/hpaste.fcgi/view?id=29048)

module Main where

import Data.List

combineNonEmpty :: (t -> Bool) -> t -> ([t] -> t) -> [t] -> [t]
combineNonEmpty isNull zero cat [] = []
combineNonEmpty isNull zero cat xs =
  let (ys, zs) = break isNull xs
      rest = if null zs
             then []
             else zero : combineNonEmpty isNull zero cat (tail zs)
  in if null ys then rest else cat ys : rest

textToParagraphs :: String -> [String]
textToParagraphs = combineNonEmpty null [] (concat . intersperse' " ") . lines

intersperse' :: a -> [a] -> [a]
intersperse' a [] = []
intersperse' a (x:xs) = x : (if null xs then [] else a : intersperse' a xs)

wordWrap :: Int -> [String] -> [[String]]
wordWrap maxLineLength [] = []
wordWrap maxLineLength ws =
  let lengths = scanl1 (\a b -> a + b + 1) $ map length ws
      wordCount = length $ takeWhile (<= maxLineLength) lengths
      wordCount' = if wordCount >= 1 then wordCount else 1
      (xs, rest) = splitAt wordCount' ws
  in xs : wordWrap maxLineLength rest

wrapParagraph :: Int -> String -> [String]
wrapParagraph maxLineLength str =
  let ws = words str
  in if null ws
     then [""]
     else map unwords $ wordWrap maxLineLength ws

wrapText :: Int -> String -> String
wrapText maxLineLength =
  unlines . concat . map (wrapParagraph maxLineLength) . textToParagraphs

main :: IO ()
main = interact (wrapText 72)


More information about the Haskell-Cafe mailing list