[project @ 2000-05-12 13:01:04 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelIO.lhs
index 321a664..187653c 100644 (file)
@@ -10,7 +10,7 @@ module IO.
 
 
 \begin{code}
-{-# OPTIONS -fcompiling-prelude -fno-implicit-prelude -#include "cbits/stgio.h" #-}
+{-# OPTIONS -fno-implicit-prelude -#include "cbits/stgio.h" #-}
 
 module PrelIO where
 
@@ -366,7 +366,8 @@ swapBuffers handle_ buf sz = do
    setBuf fo buf sz
    return (handle_{ haBuffers__ = fo_buf : haBuffers__ handle_ })
 
--- commitBuffer handle buf sz count flush
+-------------------------------------------------------------------------------
+-- commitAndReleaseBuffer handle buf sz count flush
 -- 
 -- Write the contents of the buffer 'buf' ('sz' bytes long, containing
 -- 'count' bytes of data) to handle (handle must be block or line buffered).
@@ -392,10 +393,11 @@ commitAndReleaseBuffer
        -> Int                          -- number of bytes of data in buffer
        -> Bool                         -- flush the handle afterward?
        -> IO ()
+
 commitAndReleaseBuffer hdl@(Handle h) buf sz count flush = do
       h_ <- takeMVar h
 
-       -- First deal with any possible exceptions by freeing the buffer.
+       -- First deal with any possible exceptions, by freeing the buffer.
        -- Async exceptions are blocked, but there are still some interruptible
        -- ops below.
 
@@ -418,35 +420,60 @@ commitAndReleaseBuffer hdl@(Handle h) buf sz count flush = do
 
       let ok    h_ = putMVar h h_ >> return ()
 
-      if (fo_bufSize - fo_wptr < count)        -- not enough room in handle buffer?
+         -- enough room in handle buffer for the new data?
+      if (flush || fo_bufSize - fo_wptr <= count)
+
+         -- The <= is to be sure that we never exactly fill up the
+         -- buffer, which would require a flush.  So if copying the
+         -- new data into the buffer would make the buffer full, we
+         -- just flush the existing buffer and the new data immediately,
+         -- rather than copying before flushing.
 
            then do rc <- mayBlock fo (flushFile fo)
                    if (rc < 0) 
-                       then constructErrorAndFail "commitBuffer"
+                       then constructErrorAndFail "commitAndReleaseBuffer"
                        else
-                    if flush || sz /= fo_bufSize
+                    if (flush || sz /= fo_bufSize || count == sz)
                        then do rc <- write_buf fo buf count
                                if (rc < 0)
-                                       then constructErrorAndFail "commitBuffer"
-                                       else do handle_ <- freeBuffer handle_ buf sz
-                                               ok handle_
-
-                       -- don't have to flush, and the new buffer is the
-                       -- same size as the old one, so just swap them...
+                                   then constructErrorAndFail "commitAndReleaseBuffer"
+                                   else do handle_ <- freeBuffer handle_ buf sz
+                                           ok handle_
+
+                       -- if:  (a) we don't have to flush, and
+                       --      (b) size(new buffer) == size(old buffer), and
+                       --      (c) new buffer is not full,
+                       -- we can just just swap them over...
                        else do handle_ <- swapBuffers handle_ buf sz
                                setBufWPtr fo count
                                ok handle_
 
+               -- not flushing, and there's enough room in the buffer:
+               -- just copy the data in and update bufWPtr.
            else do memcpy (plusAddr fo_buf (AddrOff# fo_wptr)) buf count
                    setBufWPtr fo (fo_wptr + count)
-                   if flush 
-                       then do rc <- mayBlock fo (flushFile fo)
-                               if (rc < 0) 
-                                       then constructErrorAndFail "commitBuffer"
-                                       else do handle_ <- freeBuffer handle_ buf sz
-                                               ok handle_
-                       else do handle_ <- freeBuffer handle_ buf sz
-                               ok handle_
+                   handle_ <- freeBuffer handle_ buf sz
+                   ok handle_
+
+--------------------------------------------------------------------------------
+-- commitBuffer handle buf sz count flush
+-- 
+-- Flushes 'count' bytes from the buffer 'buf' (size 'sz') to 'handle'.
+-- There are several cases to consider altogether:
+-- 
+-- If flush, 
+--        - flush handle buffer,
+--        - write out new buffer directly
+-- 
+-- else
+--        - if there's enough room in the handle buffer, 
+--            then copy new buf into it
+--            else flush handle buffer, then copy new buffer into it
+--
+-- Make sure that we maintain the invariant that the handle buffer is never
+-- left in a full state.  Several functions rely on this (eg. filePutc), so
+-- if we're about to exactly fill the buffer then we make sure we do a flush
+-- here (also see above in commitAndReleaseBuffer).
 
 commitBuffer
        :: Handle                       -- handle to commit to
@@ -454,6 +481,7 @@ commitBuffer
        -> Int                          -- number of bytes of data in buffer
        -> Bool                         -- flush the handle afterward?
        -> IO ()
+
 commitBuffer handle buf sz count flush = do
     wantWriteableHandle "commitBuffer" handle $ \handle_ -> do
       let fo = haFO__ handle_
@@ -463,19 +491,21 @@ commitBuffer handle buf sz count flush = do
       fo_wptr    <- getBufWPtr fo
       fo_bufSize <- getBufSize fo
 
-      (if (fo_bufSize - fo_wptr < count)  -- not enough room in handle buffer?
-           then mayBlock fo (flushFile fo)
-           else return 0)
+      new_wptr <-                       -- not enough room in handle buffer?
+       (if flush || (fo_bufSize - fo_wptr <= count)
+           then do rc <- mayBlock fo (flushFile fo)
+                   if (rc < 0) then constructErrorAndFail "commitBuffer"
+                               else return 0
+           else return fo_wptr )
 
-      if (fo_bufSize < count)          -- committed buffer too large?
+      if (flush || fo_bufSize <= count)  -- committed buffer too large?
 
            then do rc <- write_buf fo buf count
-                   if rc < 0 then constructErrorAndFail "commitBuffer"
-                             else return ()
+                   if (rc < 0) then constructErrorAndFail "commitBuffer"
+                               else return ()
 
-           else do memcpy (plusAddr fo_buf (AddrOff# fo_wptr)) buf count
-                   setBufWPtr fo (fo_wptr + count)
-                   (if flush then mayBlock fo (flushFile fo) else return 0)
+           else do memcpy (plusAddr fo_buf (AddrOff# new_wptr)) buf count
+                   setBufWPtr fo (new_wptr + count)
                    return ()
 
 write_buf fo buf 0 = return 0
@@ -485,6 +515,13 @@ write_buf fo buf count = do
        then  write_buf fo buf (count - rc) -- partial write
        else  return rc
 
+-- a version of commitBuffer that will free the buffer if an exception is 
+-- received.  DON'T use this if you intend to use the buffer again!
+checkedCommitBuffer handle buf sz count flush 
+  = catchException (commitBuffer handle buf sz count flush) 
+                  (\e -> do withHandle__ handle (\h_ -> freeBuffer h_ buf sz)
+                            throw e)
+
 foreign import "memcpy" unsafe memcpy :: Addr -> Addr -> Int -> IO ()
 \end{code}
 
@@ -514,7 +551,7 @@ writeLines handle buf bufLen s =
        let next_n = n + 1
        if next_n == bufLen || x == '\n'
         then do
-          commitBuffer hdl buf len next_n True{-needs flush-} 
+          checkedCommitBuffer hdl buf len next_n True{-needs flush-} 
           shoveString 0 xs
          else
           shoveString next_n xs
@@ -538,7 +575,7 @@ writeLines hdl buf len@(I# bufLen) s =
        let next_n = n +# 1#
        if next_n ==# bufLen || x `eqChar#` '\n'#
         then do
-          commitBuffer hdl buf len (I# next_n) True{-needs flush-} 
+          checkedCommitBuffer hdl buf len (I# next_n) True{-needs flush-} 
           shoveString 0# xs
          else
           shoveString next_n xs
@@ -560,7 +597,7 @@ writeBlocks hdl buf bufLen s =
        let next_n = n + 1
        if next_n == bufLen
         then do
-          commitBuffer hdl buf len next_n True{-needs flush-}
+          checkedCommitBuffer hdl buf len next_n True{-needs flush-}
           shoveString 0 xs
          else
           shoveString next_n xs
@@ -582,7 +619,7 @@ writeBlocks hdl buf len@(I# bufLen) s =
        let next_n = n +# 1#
        if next_n ==# bufLen
         then do
-          commitBuffer hdl buf len (I# next_n) True{-needs flush-}
+          checkedCommitBuffer hdl buf len (I# next_n) True{-needs flush-}
           shoveString 0# xs
          else
           shoveString next_n xs