#undef DEBUG_DUMP
module GHC.IO (
hWaitForInput, hGetChar, hGetLine, hGetContents, hPutChar, hPutStr,
commitBuffer',
hGetcBuffered,
hGetBuf, hGetBufNonBlocking, hPutBuf, hPutBufNonBlocking, slurpFile,
memcpy_ba_baoff,
memcpy_ptr_baoff,
memcpy_baoff_ba,
memcpy_baoff_ptr,
) where
import Foreign
import Foreign.C
import System.IO.Error
import Data.Maybe
import Control.Monad
#ifndef mingw32_HOST_OS
import System.Posix.Internals
#endif
import GHC.Enum
import GHC.Base
import GHC.IOBase
import GHC.Handle
import GHC.Real
import GHC.Num
import GHC.Show
import GHC.List
#ifdef mingw32_HOST_OS
import GHC.Conc
#endif
hWaitForInput :: Handle -> Int -> IO Bool
hWaitForInput h msecs = do
wantReadableHandle "hWaitForInput" h $ \ handle_ -> do
let ref = haBuffer handle_
buf <- readIORef ref
if not (bufferEmpty buf)
then return True
else do
if msecs < 0
then do buf' <- fillReadBuffer (haFD handle_) True
(haIsStream handle_) buf
writeIORef ref buf'
return True
else do r <- throwErrnoIfMinus1Retry "hWaitForInput" $
fdReady (haFD handle_) 0
(fromIntegral msecs)
(fromIntegral $ fromEnum $ haIsStream handle_)
if r /= 0 then do
hLookAhead' handle_
return True
else return False
foreign import ccall safe "fdReady"
fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
hGetChar :: Handle -> IO Char
hGetChar handle =
wantReadableHandle "hGetChar" handle $ \handle_ -> do
let fd = haFD handle_
ref = haBuffer handle_
buf <- readIORef ref
if not (bufferEmpty buf)
then hGetcBuffered fd ref buf
else do
case haBufferMode handle_ of
LineBuffering -> do
new_buf <- fillReadBuffer fd True (haIsStream handle_) buf
hGetcBuffered fd ref new_buf
BlockBuffering _ -> do
new_buf <- fillReadBuffer fd True (haIsStream handle_) buf
hGetcBuffered fd ref new_buf
NoBuffering -> do
let raw = bufBuf buf
r <- readRawBuffer "hGetChar" fd (haIsStream handle_) raw 0 1
if r == 0
then ioe_EOF
else do (c,_) <- readCharFromBuffer raw 0
return c
hGetcBuffered :: FD -> IORef Buffer -> Buffer -> IO Char
hGetcBuffered _ ref buf@Buffer{ bufBuf=b, bufRPtr=r0, bufWPtr=w }
= do (c, r) <- readCharFromBuffer b r0
let new_buf | r == w = buf{ bufRPtr=0, bufWPtr=0 }
| otherwise = buf{ bufRPtr=r }
writeIORef ref new_buf
return c
hGetLine :: Handle -> IO String
hGetLine h = do
m <- wantReadableHandle "hGetLine" h $ \ handle_ -> do
case haBufferMode handle_ of
NoBuffering -> return Nothing
LineBuffering -> do
l <- hGetLineBuffered handle_
return (Just l)
BlockBuffering _ -> do
l <- hGetLineBuffered handle_
return (Just l)
case m of
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__ -> IORef Buffer -> Buffer -> [String]
-> IO String
hGetLineBufferedLoop handle_ ref
buf@Buffer{ bufRPtr=r0, bufWPtr=w, bufBuf=raw0 } xss =
let
loop raw r
| r == w = return (False, w)
| otherwise = do
(c,r') <- readCharFromBuffer raw r
if c == '\n'
then return (True, r)
else loop raw r'
in do
(eol, off) <- loop raw0 r0
#ifdef DEBUG_DUMP
puts ("hGetLineBufferedLoop: r=" ++ show r0 ++ ", w=" ++ show w ++ ", off=" ++ show off ++ "\n")
#endif
xs <- unpack raw0 r0 off
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 -> 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 -> Bool -> Bool -> Buffer -> IO (Maybe Buffer)
maybeFillReadBuffer fd is_line is_stream buf
= catch
(do buf' <- fillReadBuffer fd is_line is_stream buf
return (Just buf')
)
(\e -> do if isEOFError e
then return Nothing
else ioError e)
unpack :: RawBuffer -> Int -> Int -> IO [Char]
unpack _ _ 0 = return ""
unpack buf (I# r) (I# len) = IO $ \s -> unpackRB [] (len -# 1#) s
where
unpackRB acc i s
| i <# r = (# s, acc #)
| otherwise =
case readCharArray# buf i s of
(# s', ch #) -> unpackRB (C# ch : acc) (i -# 1#) s'
hGetLineUnBuffered :: Handle -> IO String
hGetLineUnBuffered h = do
c <- hGetChar h
if c == '\n' then
return ""
else do
l <- getRest
return (c:l)
where
getRest = do
c <-
catch
(hGetChar h)
(\ err -> do
if isEOFError err then
return '\n'
else
ioError err)
if c == '\n' then
return ""
else do
s <- getRest
return (c:s)
hGetContents :: Handle -> IO String
hGetContents handle =
withHandle "hGetContents" handle $ \handle_ ->
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
AppendHandle -> ioe_notReadable
WriteHandle -> ioe_notReadable
_ -> do xs <- lazyRead handle
return (handle_{ haType=SemiClosedHandle}, xs )
lazyRead :: Handle -> IO String
lazyRead handle =
unsafeInterleaveIO $
withHandle "lazyRead" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> return (handle_, "")
SemiClosedHandle -> lazyRead' handle handle_
_ -> ioException
(IOError (Just handle) IllegalOperation "lazyRead"
"illegal handle type" Nothing)
lazyRead' :: Handle -> Handle__ -> IO (Handle__, [Char])
lazyRead' h handle_ = do
let ref = haBuffer handle_
fd = haFD handle_
buf <- readIORef ref
if not (bufferEmpty buf)
then lazyReadHaveBuffer h handle_ fd ref buf
else do
case haBufferMode handle_ of
NoBuffering -> do
let raw = bufBuf buf
r <- readRawBuffer "lazyRead" fd (haIsStream handle_) raw 0 1
if r == 0
then do (handle_', _) <- hClose_help handle_
return (handle_', "")
else do (c,_) <- readCharFromBuffer raw 0
rest <- lazyRead h
return (handle_, c : rest)
LineBuffering -> lazyReadBuffered h handle_ fd ref buf
BlockBuffering _ -> lazyReadBuffered h handle_ fd ref buf
lazyReadBuffered :: Handle -> Handle__ -> FD -> IORef Buffer -> Buffer
-> IO (Handle__, [Char])
lazyReadBuffered h handle_ fd ref buf = do
catch
(do buf' <- fillReadBuffer fd True (haIsStream handle_) buf
lazyReadHaveBuffer h handle_ fd ref buf'
)
(\_ -> do (handle_', _) <- hClose_help handle_
return (handle_', "")
)
lazyReadHaveBuffer :: Handle -> Handle__ -> FD -> IORef Buffer -> Buffer -> IO (Handle__, [Char])
lazyReadHaveBuffer h handle_ _ ref buf = do
more <- lazyRead h
writeIORef ref buf{ bufRPtr=0, bufWPtr=0 }
s <- unpackAcc (bufBuf buf) (bufRPtr buf) (bufWPtr buf) more
return (handle_, s)
unpackAcc :: RawBuffer -> Int -> Int -> [Char] -> IO [Char]
unpackAcc _ _ 0 acc = return acc
unpackAcc buf (I# r) (I# len) acc0 = IO $ \s -> unpackRB acc0 (len -# 1#) s
where
unpackRB acc i s
| i <# r = (# s, acc #)
| otherwise =
case readCharArray# buf i s of
(# s', ch #) -> unpackRB (C# ch : acc) (i -# 1#) s'
hPutChar :: Handle -> Char -> IO ()
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 ->
with (castCharToCChar c) $ \buf -> do
writeRawBufferPtr "hPutChar" fd (haIsStream handle_) buf 0 1
return ()
hPutcBuffered :: Handle__ -> Bool -> Char -> IO ()
hPutcBuffered handle_ is_line c = do
let ref = haBuffer handle_
buf <- readIORef ref
let w = bufWPtr buf
w' <- writeCharIntoBuffer (bufBuf buf) w c
let new_buf = buf{ bufWPtr = w' }
if bufferFull new_buf || is_line && c == '\n'
then do
flushed_buf <- flushWriteBuffer (haFD handle_) (haIsStream handle_) new_buf
writeIORef ref flushed_buf
else do
writeIORef ref new_buf
hPutChars :: Handle -> [Char] -> IO ()
hPutChars _ [] = return ()
hPutChars handle (c:cs) = hPutChar handle c >> hPutChars handle cs
hPutStr :: Handle -> String -> IO ()
hPutStr handle str = do
buffer_mode <- wantWritableHandle "hPutStr" handle
(\ handle_ -> do getSpareBuffer handle_)
case buffer_mode of
(NoBuffering, _) -> do
hPutChars handle str
(LineBuffering, buf) -> do
writeLines handle buf str
(BlockBuffering _, buf) -> do
writeBlocks handle buf str
getSpareBuffer :: Handle__ -> IO (BufferMode, Buffer)
getSpareBuffer Handle__{haBuffer=ref,
haBuffers=spare_ref,
haBufferMode=mode}
= do
case mode of
NoBuffering -> return (mode, error "no buffer!")
_ -> do
bufs <- readIORef spare_ref
buf <- readIORef ref
case bufs of
BufferListCons b rest -> do
writeIORef spare_ref rest
return ( mode, newEmptyBuffer b WriteBuffer (bufSize buf))
BufferListNil -> do
new_buf <- allocateBuffer (bufSize buf) WriteBuffer
return (mode, new_buf)
writeLines :: Handle -> Buffer -> String -> IO ()
writeLines hdl Buffer{ bufBuf=raw, bufSize=len } s =
let
shoveString :: Int -> [Char] -> IO ()
shoveString n cs | n == len = do
new_buf <- commitBuffer hdl raw len n True False
writeLines hdl new_buf cs
shoveString n [] = do
commitBuffer hdl raw len n False True
return ()
shoveString n (c:cs) = do
n' <- writeCharIntoBuffer raw n c
if (c == '\n')
then do
new_buf <- commitBuffer hdl raw len n' True False
writeLines hdl new_buf cs
else
shoveString n' cs
in
shoveString 0 s
writeBlocks :: Handle -> Buffer -> String -> IO ()
writeBlocks hdl Buffer{ bufBuf=raw, bufSize=len } s =
let
shoveString :: Int -> [Char] -> IO ()
shoveString n cs | n == len = do
new_buf <- commitBuffer hdl raw len n True False
writeBlocks hdl new_buf cs
shoveString n [] = do
commitBuffer hdl raw len n False True
return ()
shoveString n (c:cs) = do
n' <- writeCharIntoBuffer raw n c
shoveString n' cs
in
shoveString 0 s
commitBuffer
:: Handle
-> RawBuffer -> Int
-> Int
-> Bool
-> Bool
-> IO Buffer
commitBuffer hdl raw sz@(I# _) count@(I# _) flush release = do
wantWritableHandle "commitAndReleaseBuffer" hdl $
commitBuffer' raw sz count flush release
commitBuffer' :: RawBuffer -> Int -> Int -> Bool -> Bool -> Handle__
-> IO Buffer
commitBuffer' raw sz@(I# _) count@(I# _) flush release
handle_@Handle__{ haFD=fd, haBuffer=ref, haBuffers=spare_buf_ref } = do
#ifdef DEBUG_DUMP
puts ("commitBuffer: sz=" ++ show sz ++ ", count=" ++ show count
++ ", flush=" ++ show flush ++ ", release=" ++ show release ++"\n")
#endif
old_buf@Buffer{ bufBuf=old_raw, bufWPtr=w, bufSize=size }
<- readIORef ref
buf_ret <-
if (not flush && (size w > count))
then do memcpy_baoff_ba old_raw (fromIntegral w) raw (fromIntegral count)
writeIORef ref old_buf{ bufWPtr = w + count }
return (newEmptyBuffer raw WriteBuffer sz)
else do flushed_buf <- flushWriteBuffer fd (haIsStream handle_) old_buf
let this_buf =
Buffer{ bufBuf=raw, bufState=WriteBuffer,
bufRPtr=0, bufWPtr=count, bufSize=sz }
if (not flush && sz == size && count /= sz)
then do
writeIORef ref this_buf
return flushed_buf
else do
flushWriteBuffer fd (haIsStream handle_) this_buf
writeIORef ref flushed_buf
if sz == size
then return (newEmptyBuffer raw WriteBuffer sz)
else allocateBuffer size WriteBuffer
case buf_ret of
Buffer{ bufSize=buf_ret_sz, bufBuf=buf_ret_raw } -> do
if release && buf_ret_sz == size
then do
spare_bufs <- readIORef spare_buf_ref
writeIORef spare_buf_ref
(BufferListCons buf_ret_raw spare_bufs)
return buf_ret
else
return buf_ret
hPutBuf :: Handle
-> Ptr a
-> Int
-> IO ()
hPutBuf h ptr count = do hPutBuf' h ptr count True; return ()
hPutBufNonBlocking
:: Handle
-> Ptr a
-> Int
-> IO Int
hPutBufNonBlocking h ptr count = hPutBuf' h ptr count False
hPutBuf':: Handle
-> Ptr a
-> Int
-> Bool
-> IO Int
hPutBuf' handle ptr count can_block
| count == 0 = return 0
| count < 0 = illegalBufferSize handle "hPutBuf" count
| otherwise =
wantWritableHandle "hPutBuf" handle $
\ Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } ->
bufWrite fd ref is_stream ptr count can_block
bufWrite :: FD -> IORef Buffer -> Bool -> Ptr a -> Int -> Bool -> IO Int
bufWrite fd ref is_stream ptr count can_block =
seq count $ seq fd $ do
old_buf@Buffer{ bufBuf=old_raw, bufWPtr=w, bufSize=size }
<- readIORef ref
if (size w > count)
then do memcpy_baoff_ptr old_raw (fromIntegral w) ptr (fromIntegral count)
writeIORef ref old_buf{ bufWPtr = w + count }
return count
else do flushed_buf <- flushWriteBuffer fd is_stream old_buf
writeIORef ref flushed_buf
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 bytes0 = loop 0 bytes0
where
loop :: Int -> Int -> IO ()
loop _ bytes | bytes <= 0 = return ()
loop off bytes = do
r <- fromIntegral `liftM`
writeRawBufferPtr "writeChunk" fd is_stream ptr
off (fromIntegral bytes)
loop (off + r) (bytes r)
writeChunkNonBlocking :: FD -> Bool -> Ptr a -> Int -> IO Int
writeChunkNonBlocking fd
#ifndef mingw32_HOST_OS
_
#else
is_stream
#endif
ptr bytes0 = loop 0 bytes0
where
loop :: Int -> Int -> IO Int
loop off bytes | bytes <= 0 = return off
loop off bytes = do
#ifndef mingw32_HOST_OS
ssize <- c_write 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 (fromIntegral 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 :: Handle -> Ptr a -> Int -> IO Int
hGetBuf h ptr count
| count == 0 = return 0
| count < 0 = illegalBufferSize h "hGetBuf" count
| otherwise =
wantReadableHandle "hGetBuf" h $
\ Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
bufRead fd ref is_stream ptr 0 count
bufRead :: FD -> IORef Buffer -> Bool -> Ptr a -> Int -> Int -> IO Int
bufRead fd ref is_stream ptr so_far count =
seq fd $ seq so_far $ seq count $ do
buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r, bufSize=sz } <- readIORef ref
if bufferEmpty buf
then if count > sz
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
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 (fromIntegral 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 (fromIntegral r) (fromIntegral count)
writeIORef ref buf{ bufRPtr = r + count }
return (so_far + count)
else do
memcpy_ptr_baoff ptr raw (fromIntegral 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
rest <- readChunk fd is_stream ptr' remaining
return (so_far' + rest)
readChunk :: FD -> Bool -> Ptr a -> Int -> IO Int
readChunk fd is_stream ptr bytes0 = loop 0 bytes0
where
loop :: Int -> Int -> IO Int
loop off bytes | bytes <= 0 = return off
loop off bytes = do
r <- fromIntegral `liftM`
readRawBufferPtr "readChunk" fd is_stream
(castPtr ptr) off (fromIntegral bytes)
if r == 0
then return off
else loop (off + r) (bytes r)
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__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
bufReadNonBlocking fd ref is_stream ptr 0 count
bufReadNonBlocking :: FD -> IORef Buffer -> Bool -> Ptr a -> Int -> Int
-> IO Int
bufReadNonBlocking fd ref is_stream ptr so_far count =
seq fd $ seq so_far $ seq count $ do
buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r, bufSize=sz } <- readIORef ref
if bufferEmpty buf
then if count > sz
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')
}
else do
let avail = w r
if (count == avail)
then do
memcpy_ptr_baoff ptr raw (fromIntegral 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 (fromIntegral r) (fromIntegral count)
writeIORef ref buf{ bufRPtr = r + count }
return (so_far + count)
else do
memcpy_ptr_baoff ptr raw (fromIntegral 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 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
fromIntegral `liftM`
readRawBufferPtrNoBlock "readChunkNonBlocking" fd is_stream
(castPtr ptr) 0 (fromIntegral bytes)
slurpFile :: FilePath -> IO (Ptr (), Int)
slurpFile fname = do
handle <- openFile fname ReadMode
sz <- hFileSize handle
if sz > fromIntegral (maxBound::Int) then
ioError (userError "slurpFile: file too big")
else do
let sz_i = fromIntegral sz
if sz_i == 0 then return (nullPtr, 0) else do
chunk <- mallocBytes sz_i
r <- hGetBuf handle chunk sz_i
hClose handle
return (chunk, r)
foreign import ccall unsafe "__hscore_memcpy_src_off"
memcpy_ba_baoff :: RawBuffer -> RawBuffer -> CInt -> CSize -> IO (Ptr ())
foreign import ccall unsafe "__hscore_memcpy_src_off"
memcpy_ptr_baoff :: Ptr a -> RawBuffer -> CInt -> CSize -> IO (Ptr ())
foreign import ccall unsafe "__hscore_memcpy_dst_off"
memcpy_baoff_ba :: RawBuffer -> CInt -> RawBuffer -> CSize -> IO (Ptr ())
foreign import ccall unsafe "__hscore_memcpy_dst_off"
memcpy_baoff_ptr :: RawBuffer -> CInt -> Ptr a -> CSize -> IO (Ptr ())
illegalBufferSize :: Handle -> String -> Int -> IO a
illegalBufferSize handle fn sz =
ioException (IOError (Just handle)
InvalidArgument fn
("illegal buffer size " ++ showsPrec 9 sz [])
Nothing)