Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Bill Atkins
Right, but if you use Prelude.interact, as in my example, you don't have to 
worry about the EOF checking yourself - it's all handled for you.  And if you 
use a functional style, your code will be simpler and more testable - otherwise 
you might as well just use an imperative language.

Here's a slightly better version (uses splitAt):

maxLineLength :: Int
maxLineLength = 72

wrapLine :: String - [String]
wrapLine  = []
wrapLine line 
  | length line = maxLineLength= [line]
  | otherwise= let (line, rest) = 
splitAt maxLineLength line in
 line : 
wrapLine rest

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

On Saturday Aug 14, 2010, at 12:38 AM, michael rice wrote:

 Hi Bill,
 
 Each quote of the input is on a single line. I want to unwrap lines greater 
 than 72 characters, i.e., break them into several lines each = 72 
 characters, but I don't want to break up words. and I want to retain the 
 blank lines. So, my output is correct except for the error message.
 
 Michael 
 
  My input data 
 However mean your life is, meet it and live it: do not shun it and call it 
 hard names. Cultivate poverty like a garden herb, like sage. Do not trouble 
 yourself much to get new things, whether clothes or friends. Things do not 
 change, we change. Sell your clothes and keep your thoughts. God will see 
 that you do want society.
 
 Men have become the tools of their tools.
 
 I know of no more encouraging fact than the unquestioned ability of a man to 
 elevate his life by conscious endeavor.
 
 I once had a sparrow alight upon my shoulder for a moment, while I was hoeing 
 in a village garden, and I felt that I was more distinguished by that 
 circumstance that I should have been by any epaulet I could have worn.
 
 -Thoreau
  My output 
 unwrap: stdin: hGetLine: end of file   here's my eof message
 However mean your life is, meet it and live it: do not shun it and call 
 it hard names. Cultivate poverty like a garden herb, like sage. Do not 
 trouble yourself much to get new things, whether clothes or friends. 
 Things do not change, we change. Sell your clothes and keep your 
 thoughts. God will see that you do want society.
 
 Men have become the tools of their tools.
 
 I know of no more encouraging fact than the unquestioned ability of a 
 man to elevate his life by conscious endeavor.
 
 I once had a sparrow alight upon my shoulder for a moment, while I was 
 hoeing in a village garden, and I felt that I was more distinguished by 
 that circumstance that I should have been by any epaulet I could have 
 worn.
 
 -Thoreau
  Your output ==
 However mean your life is, meet it and live it: do not shun it and call 
 it hard names. Cultivate poverty like a garden herb, like sage. Do not t
 rouble yourself much to get new things, whether clothes or friends. Thin
 gs do not change, we change. Sell your clothes and keep your thoughts. G
 od will see that you do want society.
 Men have become the tools of their tools.
 I know of no more encouraging fact than the unquestioned ability of a ma
 n to elevate his life by conscious endeavor.
 I once had a sparrow alight upon my shoulder for a moment, while I was h
 oeing in a village garden, and I felt that I was more distinguished by t
 hat circumstance that I should have been by any epaulet I could have wor
 n.
 -Thoreau
 ===
 
 
 --- On Fri, 8/13/10, Bill Atkins watk...@alum.rpi.edu wrote:
 
 From: Bill Atkins watk...@alum.rpi.edu
 Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Friday, August 13, 2010, 11:13 PM
 
 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

Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Felipe Lessa
On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
  | otherwise                                        = let (line, rest) = 
 splitAt maxLineLength line in
                                                                 line : 
 wrapLine rest

I haven't tested myself, but does this work at all?  If I am reading
it correctly, this is the same as

  let (foo, rest) = splitAt maxLineLength foo
  in foo : wrapLine rest

In other words, no mention of wrapLine's argument 'line', and a
recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
should read:

  let (thisLine, rest) = splitAt maxLineLength line
  in thisLine : wrapLine rest

Cheers,

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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Bill Atkins
Oof, that's what I get for making just one little change without testing.

You're right.

On Saturday Aug 14, 2010, at 9:17 AM, Felipe Lessa wrote:

 On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
  | otherwise= let (line, rest) = 
 splitAt maxLineLength line in
 line : 
 wrapLine rest
 
 I haven't tested myself, but does this work at all?  If I am reading
 it correctly, this is the same as
 
  let (foo, rest) = splitAt maxLineLength foo
  in foo : wrapLine rest
 
 In other words, no mention of wrapLine's argument 'line', and a
 recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
 should read:
 
  let (thisLine, rest) = splitAt maxLineLength line
  in thisLine : wrapLine rest
 
 Cheers,
 
 -- 
 Felipe.

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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread michael rice
Hi Filipe, Bill

Your corrected version works, while the original didn't, but it still produces 
incorrect
output:

However mean your life is, meet it and live it: do not shun it and call 
it hard names. Cultivate poverty like a garden herb, like sage. Do not t
rouble yourself much to get new things, whether clothes or friends. Thin
gs do not change, we change. Sell your clothes and keep your thoughts. G
od will see that you do want society.
Men have become the tools of their tools.
I know of no more encouraging fact than the unquestioned ability of a ma
n to elevate his life by conscious endeavor.
I once had a sparrow alight upon my shoulder for a moment, while I was h
oeing in a village garden, and I felt that I was more distinguished by t
hat circumstance that I should have been by any epaulet I could have wor
n.
-Thoreau

I don't want to break lines in the middle of words and I want to retain the 
original structure of the text with respect to blank lines between individual 
quotes. THe only thing in the input text that should change are the lines 
longer than 72 characters, and they should be reformatted to one or more lines 
less than or equal to 72 characters.

Michael

--- On Sat, 8/14/10, Felipe Lessa felipe.le...@gmail.com wrote:

From: Felipe Lessa felipe.le...@gmail.com
Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
To: Bill Atkins watk...@alum.rpi.edu
Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
Date: Saturday, August 14, 2010, 9:17 AM

On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
  | otherwise                                        = let (line, rest) = 
 splitAt maxLineLength line in
                                                                 line : 
 wrapLine rest

I haven't tested myself, but does this work at all?  If I am reading
it correctly, this is the same as

  let (foo, rest) = splitAt maxLineLength foo
  in foo : wrapLine rest

In other words, no mention of wrapLine's argument 'line', and a
recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
should read:

  let (thisLine, rest) = splitAt maxLineLength line
  in thisLine : wrapLine rest

Cheers,

-- 
Felipe.



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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Bill Atkins
Try this one (http://gist.github.com/524460):

import Data.Char

maxLineLength :: Int
maxLineLength = 72

trim :: String - String
trim = reverse . dropSpaces . reverse . dropSpaces
  where dropSpaces = dropWhile isSpace

none :: (a - Bool) - [a] - Bool
none f = not . any f

reverseBreak :: (a - Bool) - [a] - ([a], [a])
reverseBreak f xs = (reverse before, reverse after)
  where (after, before) = break f $ reverse xs

wrapLine :: String - [String]
wrapLine  = [[]]
wrapLine line 
  | length line = maxLineLength= [line]
  | none isSpace line   = beforeMax : wrapLine afterMax
  | otherwise   = beforeSpace : (wrapLine $ afterSpace ++ 
afterMax)
where (beforeMax, afterMax)= splitAt maxLineLength line
  (beforeSpace, afterSpace) = reverseBreak isSpace beforeMax

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


On Saturday Aug 14, 2010, at 9:41 AM, michael rice wrote:

 Hi Filipe, Bill
 
 Your corrected version works, while the original didn't, but it still 
 produces incorrect
 output:
 
 However mean your life is, meet it and live it: do not shun it and call 
 it hard names. Cultivate poverty like a garden herb, like sage. Do not t
 rouble yourself much to get new things, whether clothes or friends. Thin
 gs do not change, we change. Sell your clothes and keep your thoughts. G
 od will see that you do want society.
 Men have become the tools of their tools.
 I know of no more encouraging fact than the unquestioned ability of a ma
 n to elevate his life by conscious endeavor.
 I once had a sparrow alight upon my shoulder for a moment, while I was h
 oeing in a village garden, and I felt that I was more distinguished by t
 hat circumstance that I should have been by any epaulet I could have wor
 n.
 -Thoreau
 
 I don't want to break lines in the middle of words and I want to retain the 
 original structure of the text with respect to blank lines between individual 
 quotes. THe only thing in the input text that should change are the lines 
 longer than 72 characters, and they should be reformatted to one or more 
 lines less than or equal to 72 characters.
 
 Michael
 
 --- On Sat, 8/14/10, Felipe Lessa felipe.le...@gmail.com wrote:
 
 From: Felipe Lessa felipe.le...@gmail.com
 Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
 To: Bill Atkins watk...@alum.rpi.edu
 Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
 Date: Saturday, August 14, 2010, 9:17 AM
 
 On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
   | otherwise= let (line, rest) = 
  splitAt maxLineLength line in
  line : 
  wrapLine rest
 
 I haven't tested myself, but does this work at all?  If I am reading
 it correctly, this is the same as
 
   let (foo, rest) = splitAt maxLineLength foo
   in foo : wrapLine rest
 
 In other words, no mention of wrapLine's argument 'line', and a
 recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
 should read:
 
   let (thisLine, rest) = splitAt maxLineLength line
   in thisLine : wrapLine rest
 
 Cheers,
 
 -- 
 Felipe.
 

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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Ronald Guida
On Sat, Aug 14, 2010 at 12:33 PM, Bill Atkins watk...@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)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread michael rice
Hi Bill,

Very clever.

You are an inspiration.

Michael

--- On Sat, 8/14/10, Bill Atkins watk...@alum.rpi.edu wrote:

From: Bill Atkins watk...@alum.rpi.edu
Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
To: michael rice nowg...@yahoo.com
Cc: Felipe Lessa felipe.le...@gmail.com, haskell-cafe@haskell.org
Date: Saturday, August 14, 2010, 12:33 PM

Try this one (http://gist.github.com/524460):

import Data.Char

maxLineLength :: Int
maxLineLength = 72

trim :: String - String
trim = reverse . dropSpaces . reverse . dropSpaces
  where dropSpaces = dropWhile isSpace

none :: (a - Bool) - [a] - Bool
none f = not . any f

reverseBreak :: (a - Bool) - [a] - ([a], [a])
reverseBreak f xs = (reverse before, reverse after)
  where (after, before) = break f $ reverse xs

wrapLine :: String - [String]
wrapLine  = [[]]
wrapLine line 
  | length line = maxLineLength    = [line]
  | none isSpace line               = beforeMax : wrapLine afterMax
  | otherwise                       = beforeSpace : (wrapLine $ afterSpace ++ 
afterMax)
    where (beforeMax, afterMax)    = splitAt maxLineLength line
          (beforeSpace, afterSpace) = reverseBreak isSpace beforeMax

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


On Saturday Aug 14, 2010, at 9:41 AM, michael rice wrote:

 Hi Filipe, Bill
 
 Your corrected version works, while the original didn't, but it still 
 produces incorrect
 output:
 
 However mean your life is, meet it and live it: do not shun it and call 
 it hard names. Cultivate poverty like a garden herb, like sage. Do not t
 rouble yourself much to get new things, whether clothes or friends. Thin
 gs do not change, we change. Sell your clothes and keep your thoughts. G
 od will see that you do want society.
 Men have become the tools of their tools.
 I know of no more encouraging fact than the unquestioned ability of a ma
 n to elevate his life by conscious endeavor.
 I once had a sparrow alight upon my shoulder for a moment, while I was h
 oeing in a village garden, and I felt that I was more distinguished by t
 hat circumstance that I should have been by any epaulet I could have wor
 n.
 -Thoreau
 
 I don't want to break lines in the middle of words and I want to retain the 
 original structure of the text with respect to blank lines between individual 
 quotes. THe only thing in the input text that should change are the lines 
 longer than 72 characters, and they should be reformatted to one or more 
 lines less than or equal to 72 characters.
 
 Michael
 
 --- On Sat, 8/14/10, Felipe Lessa felipe.le...@gmail.com wrote:
 
 From: Felipe Lessa felipe.le...@gmail.com
 Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
 To: Bill Atkins watk...@alum.rpi.edu
 Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
 Date: Saturday, August 14, 2010, 9:17 AM
 
 On Sat, Aug 14, 2010 at 9:59 AM, Bill Atkins watk...@alum.rpi.edu wrote:
   | otherwise                                        = let (line, rest) = 
 splitAt maxLineLength line in
                                                                  line : 
 wrapLine rest
 
 I haven't tested myself, but does this work at all?  If I am reading
 it correctly, this is the same as
 
   let (foo, rest) = splitAt maxLineLength foo
   in foo : wrapLine rest
 
 In other words, no mention of wrapLine's argument 'line', and a
 recursive call that will bottom out and be the same as 'undefined' :).
 GHC would warn you, though, if you used -Wall.  That expression
 should read:
 
   let (thisLine, rest) = splitAt maxLineLength line
   in thisLine : wrapLine rest
 
 Cheers,
 
 -- 
 Felipe.
 




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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Ben Millwood
On Sat, Aug 14, 2010 at 2:38 AM, michael rice nowg...@yahoo.com 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


While many other people have shown you why you need not necessarily
answer this question, I think it'd be helpful for you to hear the
answer anyway.
Your message is being produced because you are trying to getLine when
there is no input left. This raises an exception, which, because it is
not handled by your program, prints a diagnostic message and exits.
Strangely, it prints this before the output of your program - this
isn't terribly important, but for the sake of completeness, it's
because of the different buffering characteristics of stdout and
stderr, which confusingly mean that even though your program produces
output and then produces an error, the error is printed immediately
while the output waits until the program is terminated to be produced.
I think. Something like that, anyway.

So, how do you avoid the exception? You can use System.IO.isEOF [1] to
check if there is input available on the standard input handle:

main = do
  eof - isEOF
  when (not eof) realMain
  -- when from Control.Monad, see also: unless
 where
  realMain = do realStuff

Or you can let getLine throw the exception, but catch it and deal with
it yourself, rather than letting it kill your program.
Catching it is a little less simple, but is considerably more flexible
and powerful. The exceptions situation in Haskell is somewhat
complicated by the fact that the mechanism used by haskell98 has been
improved upon, but the new extensible mechanism is incompatible with
the old so both have to hang around. Have a look at Control.Exception
[2] and System.IO.Error [3]. In either case you have 'catch' as a sort
of basic operation, and more convenient things like 'try' which sort
of turn an exception into a pure Either result. I'd do something like
this:

main = do
  result - try getLine
  case result of
Left err - return () -- or do something diagnostic
Right  - putStrLn   main
Right line - doStuffWith line

On a more general note, your main function looks a little suspect
because it *always* recurses into itself - there's no termination
condition. A question nearly as important as how does my program know
what to do is how does it know when to stop :)

[1] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/System-IO.html#v%3AisEOF
[2] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/Control-Exception.html
[3] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/System-IO-Error.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/14/10 19:07 , Ben Millwood wrote:
 Strangely, it prints this before the output of your program - this
 isn't terribly important, but for the sake of completeness, it's
 because of the different buffering characteristics of stdout and
 stderr, which confusingly mean that even though your program produces
 output and then produces an error, the error is printed immediately
 while the output waits until the program is terminated to be produced.
 I think. Something like that, anyway.

My guess is he's redirecting stdout and stderr to the same file, and stderr
happens to get flushed by the Haskell runtime before stdout (possibly
because a flush is performed regardless when an exception is printed).  It
is, as you note, not really relevant to the actual logic error leading to
the exception.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxnJBUACgkQIn7hlCsL25X7jACgzk4uCCP/1LBDfgtRU0vfobZI
+BgAn2oabimC8tKOII6xBC+LM41oTpqd
=q1sj
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread michael rice
Thanks for the caveats.

I originally tried to write some pure functions to break up the long strings 
into ones of acceptable length, to no avail. The solution I submitted was a 
frustrated attempt to solve the problem *somehow* so I'd have something that 
worked to refer to.

I can see the benefit of separating IO from pure and will approach similar 
problems from that standpoint in the future.

Michael

--- On Sat, 8/14/10, Ben Millwood hask...@benmachine.co.uk wrote:

From: Ben Millwood hask...@benmachine.co.uk
Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, August 14, 2010, 7:07 PM

On Sat, Aug 14, 2010 at 2:38 AM, michael rice nowg...@yahoo.com 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


While many other people have shown you why you need not necessarily
answer this question, I think it'd be helpful for you to hear the
answer anyway.
Your message is being produced because you are trying to getLine when
there is no input left. This raises an exception, which, because it is
not handled by your program, prints a diagnostic message and exits.
Strangely, it prints this before the output of your program - this
isn't terribly important, but for the sake of completeness, it's
because of the different buffering characteristics of stdout and
stderr, which confusingly mean that even though your program produces
output and then produces an error, the error is printed immediately
while the output waits until the program is terminated to be produced.
I think. Something like that, anyway.

So, how do you avoid the exception? You can use System.IO.isEOF [1] to
check if there is input available on the standard input handle:

main = do
  eof - isEOF
  when (not eof) realMain
  -- when from Control.Monad, see also: unless
 where
  realMain = do realStuff

Or you can let getLine throw the exception, but catch it and deal with
it yourself, rather than letting it kill your program.
Catching it is a little less simple, but is considerably more flexible
and powerful. The exceptions situation in Haskell is somewhat
complicated by the fact that the mechanism used by haskell98 has been
improved upon, but the new extensible mechanism is incompatible with
the old so both have to hang around. Have a look at Control.Exception
[2] and System.IO.Error [3]. In either case you have 'catch' as a sort
of basic operation, and more convenient things like 'try' which sort
of turn an exception into a pure Either result. I'd do something like
this:

main = do
  result - try getLine
  case result of
    Left err - return () -- or do something diagnostic
    Right  - putStrLn   main
    Right line - doStuffWith line

On a more general note, your main function looks a little suspect
because it *always* recurses into itself - there's no termination
condition. A question nearly as important as how does my program know
what to do is how does it know when to stop :)

[1] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/System-IO.html#v%3AisEOF
[2] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/Control-Exception.html
[3] 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/System-IO-Error.html



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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-14 Thread michael rice
Nope. No redirection.

Michael

--- On Sat, 8/14/10, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
To: haskell-cafe@haskell.org
Date: Saturday, August 14, 2010, 7:17 PM

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/14/10 19:07 , Ben Millwood wrote:
 Strangely, it prints this before the output of your program - this
 isn't terribly important, but for the sake of completeness, it's
 because of the different buffering characteristics of stdout and
 stderr, which confusingly mean that even though your program produces
 output and then produces an error, the error is printed immediately
 while the output waits until the program is terminated to be produced.
 I think. Something like that, anyway.

My guess is he's redirecting stdout and stderr to the same file, and stderr
happens to get flushed by the Haskell runtime before stdout (possibly
because a flush is performed regardless when an exception is printed).  It
is, as you note, not really relevant to the actual logic error leading to
the exception.

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxnJBUACgkQIn7hlCsL25X7jACgzk4uCCP/1LBDfgtRU0vfobZI
+BgAn2oabimC8tKOII6xBC+LM41oTpqd
=q1sj
-END PGP SIGNATURE-
___
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


[Haskell-cafe] Unwrapping long lines in text files

2010-08-13 Thread michael rice
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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-13 Thread Bill Atkins
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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-13 Thread Bulat Ziganshin
Hello michael,

Saturday, August 14, 2010, 5:38:46 AM, you 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?

use isEOF function. even better, use interact


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Unwrapping long lines in text files

2010-08-13 Thread michael rice
Hi Bill,

Each quote of the input is on a single line. I want to unwrap lines greater 
than 72 characters, i.e., break them into several lines each = 72 characters, 
but I don't want to break up words. and I want to retain the blank lines. So, 
my output is correct except for the error message.

Michael 

 My input data 
However mean your life is, meet it and live it: do not shun it and call it hard 
names. Cultivate poverty like a garden herb, like sage. Do not trouble yourself 
much to get new things, whether clothes or friends. Things do not change, we 
change. Sell your clothes and keep your thoughts. God will see that you do want 
society.

Men have become the tools of their tools.

I know of no more encouraging fact than the unquestioned ability of a man to 
elevate his life by conscious endeavor.

I once had a sparrow alight upon my shoulder for a moment, while I was hoeing 
in a village garden, and I felt that I was more distinguished by that 
circumstance that I should have been by any epaulet I could have worn.

-Thoreau
 My output 
unwrap: stdin: hGetLine: end of file   here's my eof message
However mean your life is, meet it and live it: do not shun it and call 
it hard names. Cultivate poverty like a garden herb, like sage. Do not 
trouble yourself much to get new things, whether clothes or friends. 
Things do not change, we change. Sell your clothes and keep your 
thoughts. God will see that you do want society.

Men have become the tools of their tools.

I know of no more encouraging fact than the unquestioned ability of a 
man to elevate his life by conscious endeavor.

I once had a sparrow alight upon my shoulder for a moment, while I was 
hoeing in a village garden, and I felt that I was more distinguished by 
that circumstance that I should have been by any epaulet I could have 
worn.

-Thoreau
 Your output ==
However mean your life is, meet it and live it: do not shun it and call 
it hard names. Cultivate poverty like a garden herb, like sage. Do not t
rouble yourself much to get new things, whether clothes or friends. Thin
gs do not change, we change. Sell your clothes and keep your thoughts. G
od will see that you do want society.
Men have become the tools of their tools.
I know of no more encouraging fact than the unquestioned ability of a ma
n to elevate his life by conscious endeavor.
I once had a sparrow alight upon my shoulder for a moment, while I was h
oeing in a village garden, and I felt that I was more distinguished by t
hat circumstance that I should have been by any epaulet I could have wor
n.
-Thoreau
===


--- On Fri, 8/13/10, Bill Atkins watk...@alum.rpi.edu wrote:

From: Bill Atkins watk...@alum.rpi.edu
Subject: Re: [Haskell-cafe] Unwrapping long lines in text files
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Friday, August 13, 2010, 11:13 PM

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