Not sure if I understood what you're trying to do, but development will be 
easier if you minimize your IO, e.g. :

maxLineLength :: Int
maxLineLength = 72

wrapLine :: String -> [String]
wrapLine "" = []
wrapLine line 
  | length line <= maxLineLength    = [line]
  | otherwise                                        = take maxLineLength line 
: wrapLine (drop maxLineLength line)

main :: IO ()
main = interact $ unlines . concatMap wrapLine . lines

Now wrapLine is pure and you can use it more easily using GHCi.  Removing 
dependencies on IO usually makes your problem easier to test and understand and 
your code simpler.

In your example, the EOF probably happens on the call to getLine after input 
has run out.  By using Prelude.interact, we can ignore details like that and 
rely on already-written functions.

HTH,
Bill

On Friday Aug 13, 2010, at 9:38 PM, michael rice wrote:

> The program below takes a text file and unwraps all lines to 72 columns, but 
> I'm getting an end of file message at the top of my output.
> 
> How do I lose the EOF?
> 
> Michael
> 
> 
> ====== unwrap.hs ======
> 
> main = do
>     line <- getLine
>     if null line
>         then do
>                putStrLn ""
>                main
>         else
>            do
>              printList (words line) 1
>              main
> 
> 
> printList :: [String] -> Int -> IO ()
> printList [] _ = do putStrLn ""
> printList (w:[]) k = do 
>                        if k+(length w) <= 72
>                          then do
>                            putStrLn w
>                          else do
>                            putStrLn ""
>                            putStrLn w
> printList r@(w:ws) k = do 
>                          if k+(length w) <= 72
>                            then do
>                              putStr w
>                              putStr " "
>                              printList ws (k+(length w)+1)
>                            else do
>                              putStrLn ""
>                              printList r 1
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to