Re: [Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread Neil Davies

Its about the lazyness of reading the file. The handles on the file
associated (underlying readFile) is still open - hence the resource
being in use.

When you add that extra line the act of writing out the remainer
causes the rest of the input to be fully evaluated and hence the
filehandle is closed.

If you wish to overwrite the existing file you have to assure that the
file is not open for reading - just like with any file interface.

Neil

On 04/02/07, C.M.Brown [EMAIL PROTECTED] wrote:

Hi,

I am observing some rather strange behaviour with writeFile.

Say I have the following code:

answer - AbstractIO.readFile filename
let (answer2, remainder) = parseAnswer answer
if remainder ==   answer2 == 
  then do
AbstractIO.putStrLn $ completed
  else do
AbstractIO.putStrLn answer2
AbstractIO.writeFile filename remainder

With the above I get an error saying the resources to filename are
locked. If I add the line AbstractIO.putStrLn $ show (answer2, remainder)
before I call writeFile it suddenly magically works!

Has anyone seen strange behaviour like this before?

Regards,
Chris.
___
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] Strange behaviour with writeFile

2007-02-04 Thread C.M.Brown
Hi Neil,

 When you add that extra line the act of writing out the remainer
 causes the rest of the input to be fully evaluated and hence the
 filehandle is closed.

Ah, yes of course :)

I've found that:

let (answer2, remainder) = parseAnswer (force answer)

where

force  :: Eq a = a - a
force x = if x==x then x else x

Seems to do the trick.

Thanks!
Chris.

 On 04/02/07, C.M.Brown [EMAIL PROTECTED] wrote:
  Hi,
 
  I am observing some rather strange behaviour with writeFile.
 
  Say I have the following code:
 
  answer - AbstractIO.readFile filename
  let (answer2, remainder) = parseAnswer answer
  if remainder ==   answer2 == 
then do
  AbstractIO.putStrLn $ completed
else do
  AbstractIO.putStrLn answer2
  AbstractIO.writeFile filename remainder
 
  With the above I get an error saying the resources to filename are
  locked. If I add the line AbstractIO.putStrLn $ show (answer2, remainder)
  before I call writeFile it suddenly magically works!
 
  Has anyone seen strange behaviour like this before?
 
  Regards,
  Chris.
  ___
  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] Strange behaviour with writeFile

2007-02-04 Thread Donald Bruce Stewart
cmb21:
 fo/haskell-cafe,
   mailto:[EMAIL PROTECTED]
 Errors-To: [EMAIL PROTECTED]
 Status: O
 Content-Length: 778
 Lines: 27
 
 Hi,
 
 I am observing some rather strange behaviour with writeFile.
 
 Say I have the following code:
 
 answer - AbstractIO.readFile filename
 let (answer2, remainder) = parseAnswer answer
 if remainder ==   answer2 == 
   then do
 AbstractIO.putStrLn $ completed
   else do
 AbstractIO.putStrLn answer2
 AbstractIO.writeFile filename remainder
 
 With the above I get an error saying the resources to filename are
 locked. If I add the line AbstractIO.putStrLn $ show (answer2, remainder)
 before I call writeFile it suddenly magically works!

lazy IO at play. One quick fix would be to use strict IO:

import qualified Data.ByteString.Char8 as S
import Data.ByteString  (ByteString)

main = do
ans - S.readFile t   -- strict file IO
print (S.length ans)-- current size

let (x,xs) = S.splitAt 10 ans   -- parse
S.writeFile t xs

ans' - S.readFile t
print (S.length ans')-- new size

$ time ./a.out
2487212
2487202



This comes up often enough that I think we should have a strict readFile for 
Strings

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