[Haskell-beginners] too lazy parsing?
Kees Bleijenberg
k.bleijenberg at lijbrandt.nl
Mon Feb 4 11:50:24 CET 2013
module Main where
import Text.ParserCombinators.Parsec (many,many1,string, Parser, parse)
import System.IO (IOMode(..),hClose,openFile,hGetContents,hPutStrLn)
parseFile hOut fn = do
handle <- openFile fn ReadMode
cont <- hGetContents handle
print cont
let res = parse (many (string "blah")) "" cont
hClose handle
case res of
(Left err) -> hPutStrLn hOut $ "Error: " ++
(show err)
(Right goodRes) -> mapM_ (hPutStrLn hOut)
goodRes
main = do
hOut <- openFile "outp.txt" WriteMode
mapM (parseFile hOut) ["inp.txt"]
hClose hOut
I'am writing a program that parses a lot of files. Above is the simplest
program I can think of that demonstrates my problem.
The program above parses inp.txt. Inp.txt has only the word blah in it.
The output is saved in outp.txt. This file contains the word blah after
running the program. if I comment out the line 'print cont' nothing is saved
in outp.txt.
If I comment out 'print cont' and replace many with many1 in the following
line, it works again?
Can someone explain to me what is going on?
Kees
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130204/b99d96be/attachment.htm>
More information about the Beginners
mailing list