Whitespace changes only
[haskell-directory.git] / GHC / IO.hs
index 1dee43a..4d70295 100644 (file)
--- a/GHC/IO.hs
+++ b/GHC/IO.hs
@@ -1,4 +1,4 @@
-{-# OPTIONS -fno-implicit-prelude -#include "HsBase.h" #-}
+{-# OPTIONS_GHC -fno-implicit-prelude -#include "HsBase.h" #-}
 
 #undef DEBUG_DUMP
 
 --
 -----------------------------------------------------------------------------
 
+-- #hide
 module GHC.IO ( 
    hWaitForInput, hGetChar, hGetLine, hGetContents, hPutChar, hPutStr,
    commitBuffer',      -- hack, see below
    hGetcBuffered,      -- needed by ghc/compiler/utils/StringBuffer.lhs
-   hGetBuf, hPutBuf, slurpFile,
+   hGetBuf, hGetBufNonBlocking, hPutBuf, hPutBufNonBlocking, slurpFile,
    memcpy_ba_baoff,
    memcpy_ptr_baoff,
    memcpy_baoff_ba,
@@ -44,7 +45,10 @@ import GHC.Num
 import GHC.Show
 import GHC.List
 import GHC.Exception    ( ioError, catch )
+
+#ifdef mingw32_HOST_OS
 import GHC.Conc
+#endif
 
 -- ---------------------------------------------------------------------------
 -- Simple input operations
@@ -59,9 +63,16 @@ import GHC.Conc
 -- It returns 'True' as soon as input is available on @hdl@,
 -- or 'False' if no input is available within @t@ milliseconds.
 --
+-- If @t@ is less than zero, then @hWaitForInput@ waits indefinitely.
+--
 -- This operation may fail with:
 --
 --  * 'isEOFError' if the end of file has been reached.
+--
+-- NOTE for GHC users: unless you use the @-threaded@ flag,
+-- @hWaitForInput t@ where @t >= 0@ will block all other Haskell
+-- threads for the duration of the call.  It behaves like a
+-- @safe@ foreign call in this respect.
 
 hWaitForInput :: Handle -> Int -> IO Bool
 hWaitForInput h msecs = do
@@ -73,11 +84,17 @@ hWaitForInput h msecs = do
        then return True
        else do
 
-  r <- throwErrnoIfMinus1Retry "hWaitForInput"
-         (inputReady (fromIntegral (haFD handle_)) (fromIntegral msecs) (haIsStream handle_))
-  return (r /= 0)
-
-foreign import ccall unsafe "inputReady"
+  if msecs < 0 
+       then do buf' <- fillReadBuffer (haFD handle_) True 
+                               (haIsStream handle_) buf
+               writeIORef ref buf'
+               return True
+       else do r <- throwErrnoIfMinus1Retry "hWaitForInput" $
+                       inputReady (fromIntegral (haFD handle_)) 
+                          (fromIntegral msecs) (haIsStream handle_)
+               return (r /= 0)
+
+foreign import ccall safe "inputReady"
   inputReady :: CInt -> CInt -> Bool -> IO CInt
 
 -- ---------------------------------------------------------------------------
@@ -161,24 +178,25 @@ hGetLine h = do
        Nothing -> hGetLineUnBuffered h
        Just l  -> return l
 
-
+hGetLineBuffered :: Handle__ -> IO String
 hGetLineBuffered handle_ = do
   let ref = haBuffer handle_
   buf <- readIORef ref
   hGetLineBufferedLoop handle_ ref buf []
 
-
-hGetLineBufferedLoop handle_ ref 
-       buf@Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } xss =
-  let 
-       -- find the end-of-line character, if there is one
-       loop raw r
-          | r == w = return (False, w)
-          | otherwise =  do
-               (c,r') <- readCharFromBuffer raw r
-               if c == '\n' 
-                  then return (True, r) -- NB. not r': don't include the '\n'
-                  else loop raw r'
+hGetLineBufferedLoop :: Handle__ -> IORef Buffer -> Buffer -> [String]
+                     -> IO String
+hGetLineBufferedLoop handle_ ref
+        buf@Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } xss =
+  let
+        -- find the end-of-line character, if there is one
+        loop raw r
+           | r == w = return (False, w)
+           | otherwise =  do
+                (c,r') <- readCharFromBuffer raw r
+                if c == '\n'
+                   then return (True, r) -- NB. not r': don't include the '\n'
+                   else loop raw r'
   in do
   (eol, off) <- loop raw r
 
@@ -191,24 +209,24 @@ hGetLineBufferedLoop handle_ ref
   -- if eol == True, then off is the offset of the '\n'
   -- otherwise off == w and the buffer is now empty.
   if eol
-       then do if (w == off + 1)
-                       then writeIORef ref buf{ bufRPtr=0, bufWPtr=0 }
-                       else writeIORef ref buf{ bufRPtr = off + 1 }
-               return (concat (reverse (xs:xss)))
-       else do
-            maybe_buf <- maybeFillReadBuffer (haFD handle_) True (haIsStream handle_)
-                               buf{ bufWPtr=0, bufRPtr=0 }
-            case maybe_buf of
-               -- Nothing indicates we caught an EOF, and we may have a
-               -- partial line to return.
-               Nothing -> do
-                    writeIORef ref buf{ bufRPtr=0, bufWPtr=0 }
-                    let str = concat (reverse (xs:xss))
-                    if not (null str)
-                       then return str
-                       else ioe_EOF
-               Just new_buf -> 
-                    hGetLineBufferedLoop handle_ ref new_buf (xs:xss)
+        then do if (w == off + 1)
+                        then writeIORef ref buf{ bufRPtr=0, bufWPtr=0 }
+                        else writeIORef ref buf{ bufRPtr = off + 1 }
+                return (concat (reverse (xs:xss)))
+        else do
+             maybe_buf <- maybeFillReadBuffer (haFD handle_) True (haIsStream handle_)
+                                buf{ bufWPtr=0, bufRPtr=0 }
+             case maybe_buf of
+                -- Nothing indicates we caught an EOF, and we may have a
+                -- partial line to return.
+                Nothing -> do
+                     writeIORef ref buf{ bufRPtr=0, bufWPtr=0 }
+                     let str = concat (reverse (xs:xss))
+                     if not (null str)
+                        then return str
+                        else ioe_EOF
+                Just new_buf ->
+                     hGetLineBufferedLoop handle_ ref new_buf (xs:xss)
 
 
 maybeFillReadBuffer fd is_line is_stream buf
@@ -386,15 +404,15 @@ unpackAcc buf (I# r) (I# len) acc = IO $ \s -> unpack acc (len -# 1#) s
 --  * 'isPermissionError' if another system resource limit would be exceeded.
 
 hPutChar :: Handle -> Char -> IO ()
-hPutChar handle c = 
-    c `seq` do   -- must evaluate c before grabbing the handle lock
+hPutChar handle c = do
+    c `seq` return ()
     wantWritableHandle "hPutChar" handle $ \ handle_  -> do
     let fd = haFD handle_
     case haBufferMode handle_ of
        LineBuffering    -> hPutcBuffered handle_ True  c
        BlockBuffering _ -> hPutcBuffered handle_ False c
        NoBuffering      ->
-               withObject (castCharToCChar c) $ \buf -> do
+               with (castCharToCChar c) $ \buf -> do
                  writeRawBufferPtr "hPutChar" (fromIntegral fd) (haIsStream handle_) buf 0 1
                  return ()
 
@@ -547,7 +565,7 @@ commitBuffer
 
 commitBuffer hdl raw sz@(I# _) count@(I# _) flush release = do
   wantWritableHandle "commitAndReleaseBuffer" hdl $
-     commitBuffer' hdl raw sz count flush release
+     commitBuffer' raw sz count flush release
 
 -- Explicitly lambda-lift this function to subvert GHC's full laziness
 -- optimisations, which otherwise tends to float out subexpressions
@@ -560,7 +578,7 @@ commitBuffer hdl raw sz@(I# _) count@(I# _) flush release = do
 --
 -- This hack is a fairly big win for hPutStr performance.  --SDM 18/9/2001
 --
-commitBuffer' hdl raw sz@(I# _) count@(I# _) flush release
+commitBuffer' raw sz@(I# _) count@(I# _) flush release
   handle_@Handle__{ haFD=fd, haBuffer=ref, haBuffers=spare_buf_ref } = do
 
 #ifdef DEBUG_DUMP
@@ -646,29 +664,52 @@ hPutBuf :: Handle                 -- handle to write to
        -> Ptr a                        -- address of buffer
        -> Int                          -- number of bytes of data in buffer
        -> IO ()
-hPutBuf handle ptr count
-  | count == 0 = return ()
+hPutBuf h ptr count = do hPutBuf' h ptr count True; return ()
+
+hPutBufNonBlocking
+       :: Handle                       -- handle to write to
+       -> Ptr a                        -- address of buffer
+       -> Int                          -- number of bytes of data in buffer
+       -> IO Int                       -- returns: number of bytes written
+hPutBufNonBlocking h ptr count = hPutBuf' h ptr count False
+
+hPutBuf':: Handle                      -- handle to write to
+       -> Ptr a                        -- address of buffer
+       -> Int                          -- number of bytes of data in buffer
+       -> Bool                         -- allow blocking?
+       -> IO Int
+hPutBuf' handle ptr count can_block
+  | count == 0 = return 0
   | count <  0 = illegalBufferSize handle "hPutBuf" count
   | otherwise = 
     wantWritableHandle "hPutBuf" handle $ 
-      \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
-
-        old_buf@Buffer{ bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size }
-         <- readIORef ref
-
-        -- enough room in handle buffer?
-        if (size - w > count)
-               -- There's enough room in the buffer:
-               -- just copy the data in and update bufWPtr.
-           then do memcpy_baoff_ptr old_raw w ptr (fromIntegral count)
-                   writeIORef ref old_buf{ bufWPtr = w + count }
-                   return ()
-
-               -- else, we have to flush
-           else do flushed_buf <- flushWriteBuffer fd is_stream old_buf
-                   writeIORef ref flushed_buf
-                   -- ToDo: should just memcpy instead of writing if possible
-                   writeChunk fd is_stream (castPtr ptr) count
+      \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> 
+         bufWrite fd ref is_stream ptr count can_block
+
+bufWrite fd ref is_stream ptr count can_block =
+  seq count $ seq fd $ do  -- strictness hack
+  old_buf@Buffer{ bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size }
+     <- readIORef ref
+
+  -- enough room in handle buffer?
+  if (size - w > count)
+       -- There's enough room in the buffer:
+       -- just copy the data in and update bufWPtr.
+       then do memcpy_baoff_ptr old_raw w ptr (fromIntegral count)
+               writeIORef ref old_buf{ bufWPtr = w + count }
+               return count
+
+       -- else, we have to flush
+       else do flushed_buf <- flushWriteBuffer fd is_stream old_buf
+                       -- TODO: we should do a non-blocking flush here
+               writeIORef ref flushed_buf
+               -- if we can fit in the buffer, then just loop  
+               if count < size
+                  then bufWrite fd ref is_stream ptr count can_block
+                  else if can_block
+                          then do writeChunk fd is_stream (castPtr ptr) count
+                                  return count
+                          else writeChunkNonBlocking fd is_stream ptr count
 
 writeChunk :: FD -> Bool -> Ptr CChar -> Int -> IO ()
 writeChunk fd is_stream ptr bytes = loop 0 bytes 
@@ -682,6 +723,31 @@ writeChunk fd is_stream ptr bytes = loop 0 bytes
     -- write can't return 0
     loop (off + r) (bytes - r)
 
+writeChunkNonBlocking :: FD -> Bool -> Ptr a -> Int -> IO Int
+writeChunkNonBlocking fd is_stream ptr bytes = loop 0 bytes 
+ where
+  loop :: Int -> Int -> IO Int
+  loop off bytes | bytes <= 0 = return off
+  loop off bytes = do
+#ifndef mingw32_HOST_OS
+    ssize <- c_write (fromIntegral fd) (ptr `plusPtr` off) (fromIntegral bytes)
+    let r = fromIntegral ssize :: Int
+    if (r == -1)
+      then do errno <- getErrno
+             if (errno == eAGAIN || errno == eWOULDBLOCK)
+                then return off
+                else throwErrno "writeChunk"
+      else loop (off + r) (bytes - r)
+#else
+    (ssize, rc) <- asyncWrite fd (fromIntegral $ fromEnum is_stream)
+                                (fromIntegral bytes)
+                                (ptr `plusPtr` off)
+    let r = fromIntegral ssize :: Int
+    if r == (-1)
+      then ioError (errnoToIOError "hPutBufNonBlocking" (Errno (fromIntegral rc)) Nothing Nothing)
+      else loop (off + r) (bytes - r)
+#endif
+
 -- ---------------------------------------------------------------------------
 -- hGetBuf
 
@@ -698,33 +764,58 @@ writeChunk fd is_stream ptr bytes = loop 0 bytes
 -- is closed, 'hGetBuf' will behave as if EOF was reached.
 
 hGetBuf :: Handle -> Ptr a -> Int -> IO Int
-hGetBuf handle ptr count
+hGetBuf h ptr count
   | count == 0 = return 0
-  | count <  0 = illegalBufferSize handle "hGetBuf" count
+  | count <  0 = illegalBufferSize h "hGetBuf" count
   | otherwise = 
-      wantReadableHandle "hGetBuf" handle $ 
+      wantReadableHandle "hGetBuf" h $ 
        \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
-       buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r } <- readIORef ref
-       if bufferEmpty buf
-          then readChunk fd is_stream ptr count
+           bufRead fd ref is_stream ptr 0 count
+
+-- small reads go through the buffer, large reads are satisfied by
+-- taking data first from the buffer and then direct from the file
+-- descriptor.
+bufRead fd ref is_stream ptr so_far count =
+  seq fd $ seq so_far $ seq count $ do -- strictness hack
+  buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r, bufSize=sz } <- readIORef ref
+  if bufferEmpty buf
+     then if count > sz  -- small read?
+               then do rest <- readChunk fd is_stream ptr count
+                       return (so_far + rest)
+               else do mb_buf <- maybeFillReadBuffer fd True is_stream buf
+                       case mb_buf of
+                         Nothing -> return so_far -- got nothing, we're done
+                         Just buf' -> do
+                               writeIORef ref buf'
+                               bufRead fd ref is_stream ptr so_far count
+     else do 
+       let avail = w - r
+       if (count == avail)
+          then do 
+               memcpy_ptr_baoff ptr raw r (fromIntegral count)
+               writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
+               return (so_far + count)
+          else do
+       if (count < avail)
+          then do 
+               memcpy_ptr_baoff ptr raw r (fromIntegral count)
+               writeIORef ref buf{ bufRPtr = r + count }
+               return (so_far + count)
+          else do
+  
+       memcpy_ptr_baoff ptr raw r (fromIntegral avail)
+       writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
+       let remaining = count - avail
+           so_far' = so_far + avail
+           ptr' = ptr `plusPtr` avail
+
+       if remaining < sz
+          then bufRead fd ref is_stream ptr' so_far' remaining
           else do 
-               let avail = w - r
-               copied <- if (count >= avail)
-                           then do 
-                               memcpy_ptr_baoff ptr raw r (fromIntegral avail)
-                               writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
-                               return avail
-                           else do
-                               memcpy_ptr_baoff ptr raw r (fromIntegral count)
-                               writeIORef ref buf{ bufRPtr = r + count }
-                               return count
-
-               let remaining = count - copied
-               if remaining > 0 
-                  then do rest <- readChunk fd is_stream (ptr `plusPtr` copied) remaining
-                          return (rest + copied)
-                  else return count
-               
+
+       rest <- readChunk fd is_stream ptr' remaining
+       return (so_far' + rest)
+
 readChunk :: FD -> Bool -> Ptr a -> Int -> IO Int
 readChunk fd is_stream ptr bytes = loop 0 bytes 
  where
@@ -738,6 +829,99 @@ readChunk fd is_stream ptr bytes = loop 0 bytes
        then return off
        else loop (off + r) (bytes - r)
 
+
+-- | 'hGetBufNonBlocking' @hdl buf count@ reads data from the handle @hdl@
+-- into the buffer @buf@ until either EOF is reached, or
+-- @count@ 8-bit bytes have been read, or there is no more data available
+-- to read immediately.
+--
+-- 'hGetBufNonBlocking' is identical to 'hGetBuf', except that it will
+-- never block waiting for data to become available, instead it returns
+-- only whatever data is available.  To wait for data to arrive before
+-- calling 'hGetBufNonBlocking', use 'hWaitForInput'.
+--
+-- If the handle is a pipe or socket, and the writing end
+-- is closed, 'hGetBufNonBlocking' will behave as if EOF was reached.
+--
+hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int
+hGetBufNonBlocking h ptr count
+  | count == 0 = return 0
+  | count <  0 = illegalBufferSize h "hGetBufNonBlocking" count
+  | otherwise = 
+      wantReadableHandle "hGetBufNonBlocking" h $ 
+       \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
+           bufReadNonBlocking fd ref is_stream ptr 0 count
+
+bufReadNonBlocking fd ref is_stream ptr so_far count =
+  seq fd $ seq so_far $ seq count $ do -- strictness hack
+  buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r, bufSize=sz } <- readIORef ref
+  if bufferEmpty buf
+     then if count > sz  -- large read?
+               then do rest <- readChunkNonBlocking fd is_stream ptr count
+                       return (so_far + rest)
+               else do buf' <- fillReadBufferWithoutBlocking fd is_stream buf
+                       case buf' of { Buffer{ bufWPtr=w }  ->
+                       if (w == 0) 
+                          then return so_far
+                          else do writeIORef ref buf'
+                                  bufReadNonBlocking fd ref is_stream ptr
+                                        so_far (min count w)
+                                 -- NOTE: new count is 'min count w'
+                                 -- so we will just copy the contents of the
+                                 -- buffer in the recursive call, and not
+                                 -- loop again.
+                       }
+     else do
+       let avail = w - r
+       if (count == avail)
+          then do 
+               memcpy_ptr_baoff ptr raw r (fromIntegral count)
+               writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
+               return (so_far + count)
+          else do
+       if (count < avail)
+          then do 
+               memcpy_ptr_baoff ptr raw r (fromIntegral count)
+               writeIORef ref buf{ bufRPtr = r + count }
+               return (so_far + count)
+          else do
+
+       memcpy_ptr_baoff ptr raw r (fromIntegral avail)
+       writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
+       let remaining = count - avail
+           so_far' = so_far + avail
+           ptr' = ptr `plusPtr` avail
+
+       -- we haven't attempted to read anything yet if we get to here.
+       if remaining < sz
+          then bufReadNonBlocking fd ref is_stream ptr' so_far' remaining
+          else do 
+
+       rest <- readChunkNonBlocking fd is_stream ptr' remaining
+       return (so_far' + rest)
+
+
+readChunkNonBlocking :: FD -> Bool -> Ptr a -> Int -> IO Int
+readChunkNonBlocking fd is_stream ptr bytes = do
+#ifndef mingw32_HOST_OS
+    ssize <- c_read (fromIntegral fd) (castPtr ptr) (fromIntegral bytes)
+    let r = fromIntegral ssize :: Int
+    if (r == -1)
+      then do errno <- getErrno
+             if (errno == eAGAIN || errno == eWOULDBLOCK)
+                then return 0
+                else throwErrno "readChunk"
+      else return r
+#else
+    fromIntegral `liftM`
+        readRawBufferPtr "readChunkNonBlocking" (fromIntegral fd) is_stream 
+                           (castPtr ptr) 0 (fromIntegral bytes)
+
+    -- we don't have non-blocking read support on Windows, so just invoke
+    -- the ordinary low-level read which will block until data is available,
+    -- but won't wait for the whole buffer to fill.
+#endif
+
 slurpFile :: FilePath -> IO (Ptr (), Int)
 slurpFile fname = do
   handle <- openFile fname ReadMode