#undef DEBUG_DUMP
#undef DEBUG
module GHC.Handle (
withHandle, withHandle', withHandle_,
wantWritableHandle, wantReadableHandle, wantSeekableHandle,
newEmptyBuffer, allocateBuffer, readCharFromBuffer, writeCharIntoBuffer,
flushWriteBufferOnly, flushWriteBuffer, flushReadBuffer,
fillReadBuffer, fillReadBufferWithoutBlocking,
readRawBuffer, readRawBufferPtr,
writeRawBuffer, writeRawBufferPtr,
#ifndef mingw32_HOST_OS
unlockFile,
#endif
ioe_closedHandle, ioe_EOF, ioe_notReadable, ioe_notWritable,
stdin, stdout, stderr,
IOMode(..), openFile, openBinaryFile, fdToHandle_stat, fdToHandle, fdToHandle',
hFileSize, hSetFileSize, hIsEOF, isEOF, hLookAhead, hSetBuffering, hSetBinaryMode,
hFlush, hDuplicate, hDuplicateTo,
hClose, hClose_help,
HandlePosition, HandlePosn(..), hGetPosn, hSetPosn,
SeekMode(..), hSeek, hTell,
hIsOpen, hIsClosed, hIsReadable, hIsWritable, hGetBuffering, hIsSeekable,
hSetEcho, hGetEcho, hIsTerminalDevice,
hShow,
#ifdef DEBUG_DUMP
puts,
#endif
) where
import Control.Monad
import Data.Bits
import Data.Maybe
import Foreign
import Foreign.C
import System.IO.Error
import System.Posix.Internals
import System.Posix.Types
import GHC.Real
import GHC.Arr
import GHC.Base
import GHC.Read ( Read )
import GHC.List
import GHC.IOBase
import GHC.Exception
import GHC.Enum
import GHC.Num ( Integer(..), Num(..) )
import GHC.Show
import GHC.Real ( toInteger )
#if defined(DEBUG_DUMP)
import GHC.Pack
#endif
import GHC.Conc
dEFAULT_OPEN_IN_BINARY_MODE = False :: Bool
newFileHandle :: FilePath -> (MVar Handle__ -> IO ()) -> Handle__ -> IO Handle
newFileHandle filepath finalizer hc = do
m <- newMVar hc
addMVarFinalizer m (finalizer m)
return (FileHandle filepath m)
withHandle :: String -> Handle -> (Handle__ -> IO (Handle__,a)) -> IO a
withHandle fun h@(FileHandle _ m) act = withHandle' fun h m act
withHandle fun h@(DuplexHandle _ m _) act = withHandle' fun h m act
withHandle' :: String -> Handle -> MVar Handle__
-> (Handle__ -> IO (Handle__,a)) -> IO a
withHandle' fun h m act =
block $ do
h_ <- takeMVar m
checkBufferInvariants h_
(h',v) <- catchException (act h_)
(\ err -> putMVar m h_ >>
case err of
IOException ex -> ioError (augmentIOError ex fun h)
_ -> throw err)
checkBufferInvariants h'
putMVar m h'
return v
withHandle_ :: String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ fun h@(FileHandle _ m) act = withHandle_' fun h m act
withHandle_ fun h@(DuplexHandle _ m _) act = withHandle_' fun h m act
withHandle_' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' fun h m act =
block $ do
h_ <- takeMVar m
checkBufferInvariants h_
v <- catchException (act h_)
(\ err -> putMVar m h_ >>
case err of
IOException ex -> ioError (augmentIOError ex fun h)
_ -> throw err)
checkBufferInvariants h_
putMVar m h_
return v
withAllHandles__ :: String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ fun h@(FileHandle _ m) act = withHandle__' fun h m act
withAllHandles__ fun h@(DuplexHandle _ r w) act = do
withHandle__' fun h r act
withHandle__' fun h w act
withHandle__' fun h m act =
block $ do
h_ <- takeMVar m
checkBufferInvariants h_
h' <- catchException (act h_)
(\ err -> putMVar m h_ >>
case err of
IOException ex -> ioError (augmentIOError ex fun h)
_ -> throw err)
checkBufferInvariants h'
putMVar m h'
return ()
augmentIOError (IOError _ iot _ str fp) fun h
= IOError (Just h) iot fun str filepath
where filepath
| Just _ <- fp = fp
| otherwise = case h of
FileHandle fp _ -> Just fp
DuplexHandle fp _ _ -> Just fp
wantWritableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantWritableHandle fun h@(FileHandle _ m) act
= wantWritableHandle' fun h m act
wantWritableHandle fun h@(DuplexHandle _ _ m) act
= wantWritableHandle' fun h m act
wantWritableHandle'
:: String -> Handle -> MVar Handle__
-> (Handle__ -> IO a) -> IO a
wantWritableHandle' fun h m act
= withHandle_' fun h m (checkWritableHandle act)
checkWritableHandle act handle_
= case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
ReadHandle -> ioe_notWritable
ReadWriteHandle -> do
let ref = haBuffer handle_
buf <- readIORef ref
new_buf <-
if not (bufferIsWritable buf)
then do b <- flushReadBuffer (haFD handle_) buf
return b{ bufState=WriteBuffer }
else return buf
writeIORef ref new_buf
act handle_
_other -> act handle_
wantReadableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle fun h@(FileHandle _ m) act
= wantReadableHandle' fun h m act
wantReadableHandle fun h@(DuplexHandle _ m _) act
= wantReadableHandle' fun h m act
wantReadableHandle'
:: String -> Handle -> MVar Handle__
-> (Handle__ -> IO a) -> IO a
wantReadableHandle' fun h m act
= withHandle_' fun h m (checkReadableHandle act)
checkReadableHandle act handle_ =
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
AppendHandle -> ioe_notReadable
WriteHandle -> ioe_notReadable
ReadWriteHandle -> do
let ref = haBuffer handle_
buf <- readIORef ref
when (bufferIsWritable buf) $ do
new_buf <- flushWriteBuffer (haFD handle_) (haIsStream handle_) buf
writeIORef ref new_buf{ bufState=ReadBuffer }
act handle_
_other -> act handle_
wantSeekableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantSeekableHandle fun h@(DuplexHandle _ _ _) _act =
ioException (IOError (Just h) IllegalOperation fun
"handle is not seekable" Nothing)
wantSeekableHandle fun h@(FileHandle _ m) act =
withHandle_' fun h m (checkSeekableHandle act)
checkSeekableHandle act handle_ =
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
AppendHandle -> ioe_notSeekable
_ | haIsBin handle_ || tEXT_MODE_SEEK_ALLOWED -> act handle_
| otherwise -> ioe_notSeekable_notBin
ioe_closedHandle, ioe_EOF,
ioe_notReadable, ioe_notWritable,
ioe_notSeekable, ioe_notSeekable_notBin :: IO a
ioe_closedHandle = ioException
(IOError Nothing IllegalOperation ""
"handle is closed" Nothing)
ioe_EOF = ioException
(IOError Nothing EOF "" "" Nothing)
ioe_notReadable = ioException
(IOError Nothing IllegalOperation ""
"handle is not open for reading" Nothing)
ioe_notWritable = ioException
(IOError Nothing IllegalOperation ""
"handle is not open for writing" Nothing)
ioe_notSeekable = ioException
(IOError Nothing IllegalOperation ""
"handle is not seekable" Nothing)
ioe_notSeekable_notBin = ioException
(IOError Nothing IllegalOperation ""
"seek operations on text-mode handles are not allowed on this platform"
Nothing)
ioe_finalizedHandle fp = throw (IOException
(IOError Nothing IllegalOperation ""
"handle is finalized" (Just fp)))
ioe_bufsiz :: Int -> IO a
ioe_bufsiz n = ioException
(IOError Nothing InvalidArgument "hSetBuffering"
("illegal buffer size " ++ showsPrec 9 n []) Nothing)
stdHandleFinalizer :: FilePath -> MVar Handle__ -> IO ()
stdHandleFinalizer fp m = do
h_ <- takeMVar m
flushWriteBufferOnly h_
putMVar m (ioe_finalizedHandle fp)
handleFinalizer :: FilePath -> MVar Handle__ -> IO ()
handleFinalizer fp m = do
handle_ <- takeMVar m
case haType handle_ of
ClosedHandle -> return ()
_ -> do flushWriteBufferOnly handle_ `catchException` \_ -> return ()
hClose_handle_ handle_
return ()
putMVar m (ioe_finalizedHandle fp)
#ifdef DEBUG
checkBufferInvariants h_ = do
let ref = haBuffer h_
Buffer{ bufWPtr=w, bufRPtr=r, bufSize=size, bufState=state } <- readIORef ref
if not (
size > 0
&& r <= w
&& w <= size
&& ( r /= w || (r == 0 && w == 0) )
&& ( state /= WriteBuffer || r == 0 )
&& ( state /= WriteBuffer || w < size )
)
then error "buffer invariant violation"
else return ()
#else
checkBufferInvariants h_ = return ()
#endif
newEmptyBuffer :: RawBuffer -> BufferState -> Int -> Buffer
newEmptyBuffer b state size
= Buffer{ bufBuf=b, bufRPtr=0, bufWPtr=0, bufSize=size, bufState=state }
allocateBuffer :: Int -> BufferState -> IO Buffer
allocateBuffer sz@(I# size) state = IO $ \s ->
case newPinnedByteArray# size s of { (# s, b #) ->
(# s, newEmptyBuffer b state sz #) }
writeCharIntoBuffer :: RawBuffer -> Int -> Char -> IO Int
writeCharIntoBuffer slab (I# off) (C# c)
= IO $ \s -> case writeCharArray# slab off c s of
s -> (# s, I# (off +# 1#) #)
readCharFromBuffer :: RawBuffer -> Int -> IO (Char, Int)
readCharFromBuffer slab (I# off)
= IO $ \s -> case readCharArray# slab off s of
(# s, c #) -> (# s, (C# c, I# (off +# 1#)) #)
getBuffer :: FD -> BufferState -> IO (IORef Buffer, BufferMode)
getBuffer fd state = do
buffer <- allocateBuffer dEFAULT_BUFFER_SIZE state
ioref <- newIORef buffer
is_tty <- fdIsTTY fd
let buffer_mode
| is_tty = LineBuffering
| otherwise = BlockBuffering Nothing
return (ioref, buffer_mode)
mkUnBuffer :: IO (IORef Buffer)
mkUnBuffer = do
buffer <- allocateBuffer 1 ReadBuffer
newIORef buffer
flushWriteBufferOnly :: Handle__ -> IO ()
flushWriteBufferOnly h_ = do
let fd = haFD h_
ref = haBuffer h_
buf <- readIORef ref
new_buf <- if bufferIsWritable buf
then flushWriteBuffer fd (haIsStream h_) buf
else return buf
writeIORef ref new_buf
flushBuffer :: Handle__ -> IO ()
flushBuffer h_ = do
let ref = haBuffer h_
buf <- readIORef ref
flushed_buf <-
case bufState buf of
ReadBuffer -> flushReadBuffer (haFD h_) buf
WriteBuffer -> flushWriteBuffer (haFD h_) (haIsStream h_) buf
writeIORef ref flushed_buf
flushReadBuffer :: FD -> Buffer -> IO Buffer
flushReadBuffer fd buf
| bufferEmpty buf = return buf
| otherwise = do
let off = negate (bufWPtr buf bufRPtr buf)
# ifdef DEBUG_DUMP
puts ("flushReadBuffer: new file offset = " ++ show off ++ "\n")
# endif
throwErrnoIfMinus1Retry "flushReadBuffer"
(c_lseek fd (fromIntegral off) sEEK_CUR)
return buf{ bufWPtr=0, bufRPtr=0 }
flushWriteBuffer :: FD -> Bool -> Buffer -> IO Buffer
flushWriteBuffer fd is_stream buf@Buffer{ bufBuf=b, bufRPtr=r, bufWPtr=w } =
seq fd $ do
let bytes = w r
#ifdef DEBUG_DUMP
puts ("flushWriteBuffer, fd=" ++ show fd ++ ", bytes=" ++ show bytes ++ "\n")
#endif
if bytes == 0
then return (buf{ bufRPtr=0, bufWPtr=0 })
else do
res <- writeRawBuffer "flushWriteBuffer" fd is_stream b
(fromIntegral r) (fromIntegral bytes)
let res' = fromIntegral res
if res' < bytes
then flushWriteBuffer fd is_stream (buf{ bufRPtr = r + res' })
else return buf{ bufRPtr=0, bufWPtr=0 }
fillReadBuffer :: FD -> Bool -> Bool -> Buffer -> IO Buffer
fillReadBuffer fd is_line is_stream
buf@Buffer{ bufBuf=b, bufRPtr=r, bufWPtr=w, bufSize=size } =
assert (r == 0 && w == 0) $ do
fillReadBufferLoop fd is_line is_stream buf b w size
fillReadBufferLoop fd is_line is_stream buf b w size = do
let bytes = size w
if bytes == 0
then return buf{ bufRPtr=0, bufWPtr=w }
else do
#ifdef DEBUG_DUMP
puts ("fillReadBufferLoop: bytes = " ++ show bytes ++ "\n")
#endif
res <- readRawBuffer "fillReadBuffer" fd is_stream b
(fromIntegral w) (fromIntegral bytes)
let res' = fromIntegral res
#ifdef DEBUG_DUMP
puts ("fillReadBufferLoop: res' = " ++ show res' ++ "\n")
#endif
if res' == 0
then if w == 0
then ioe_EOF
else return buf{ bufRPtr=0, bufWPtr=w }
else if res' < bytes && not is_line
then fillReadBufferLoop fd is_line is_stream buf b (w+res') size
else return buf{ bufRPtr=0, bufWPtr=w+res' }
fillReadBufferWithoutBlocking :: FD -> Bool -> Buffer -> IO Buffer
fillReadBufferWithoutBlocking fd is_stream
buf@Buffer{ bufBuf=b, bufRPtr=r, bufWPtr=w, bufSize=size } =
assert (r == 0 && w == 0) $ do
#ifdef DEBUG_DUMP
puts ("fillReadBufferLoopNoBlock: bytes = " ++ show size ++ "\n")
#endif
res <- readRawBufferNoBlock "fillReadBuffer" fd is_stream b
0 (fromIntegral size)
let res' = fromIntegral res
#ifdef DEBUG_DUMP
puts ("fillReadBufferLoopNoBlock: res' = " ++ show res' ++ "\n")
#endif
return buf{ bufRPtr=0, bufWPtr=res' }
#ifndef mingw32_HOST_OS
readRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBuffer loc fd is_nonblock buf off len
| is_nonblock = unsafe_read
| threaded = safe_read
| otherwise = do r <- throwErrnoIfMinus1 loc
(fdReady (fromIntegral fd) 0 0 False)
if r /= 0
then unsafe_read
else do threadWaitRead (fromIntegral fd); unsafe_read
where
do_read call = throwErrnoIfMinus1RetryMayBlock loc call
(threadWaitRead (fromIntegral fd))
unsafe_read = do_read (read_rawBuffer fd buf off len)
safe_read = do_read (safe_read_rawBuffer fd buf off len)
readRawBufferPtr :: String -> FD -> Bool -> Ptr CChar -> Int -> CInt -> IO CInt
readRawBufferPtr loc fd is_nonblock buf off len
| is_nonblock = unsafe_read
| threaded = safe_read
| otherwise = do r <- throwErrnoIfMinus1 loc
(fdReady (fromIntegral fd) 0 0 False)
if r /= 0
then unsafe_read
else do threadWaitRead (fromIntegral fd); unsafe_read
where
do_read call = throwErrnoIfMinus1RetryMayBlock loc call
(threadWaitRead (fromIntegral fd))
unsafe_read = do_read (read_off fd buf off len)
safe_read = do_read (safe_read_off fd buf off len)
readRawBufferNoBlock :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBufferNoBlock loc fd is_nonblock buf off len
| is_nonblock = unsafe_read
| otherwise = do r <- fdReady (fromIntegral fd) 0 0 False
if r /= 0 then safe_read
else return 0
where
do_read call = throwErrnoIfMinus1RetryOnBlock loc call (return 0)
unsafe_read = do_read (read_rawBuffer fd buf off len)
safe_read = do_read (safe_read_rawBuffer fd buf off len)
writeRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
writeRawBuffer loc fd is_nonblock buf off len
| is_nonblock = unsafe_write
| threaded = safe_write
| otherwise = do r <- fdReady (fromIntegral fd) 1 0 False
if r /= 0
then safe_write
else do threadWaitWrite (fromIntegral fd); unsafe_write
where
do_write call = throwErrnoIfMinus1RetryMayBlock loc call
(threadWaitWrite (fromIntegral fd))
unsafe_write = do_write (write_rawBuffer fd buf off len)
safe_write = do_write (safe_write_rawBuffer (fromIntegral fd) buf off len)
writeRawBufferPtr :: String -> FD -> Bool -> Ptr CChar -> Int -> CInt -> IO CInt
writeRawBufferPtr loc fd is_nonblock buf off len
| is_nonblock = unsafe_write
| threaded = safe_write
| otherwise = do r <- fdReady (fromIntegral fd) 1 0 False
if r /= 0
then safe_write
else do threadWaitWrite (fromIntegral fd); unsafe_write
where
do_write call = throwErrnoIfMinus1RetryMayBlock loc call
(threadWaitWrite (fromIntegral fd))
unsafe_write = do_write (write_off fd buf off len)
safe_write = do_write (safe_write_off (fromIntegral fd) buf off len)
foreign import ccall unsafe "__hscore_PrelHandle_read"
read_rawBuffer :: CInt -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall unsafe "__hscore_PrelHandle_read"
read_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
foreign import ccall unsafe "__hscore_PrelHandle_write"
write_rawBuffer :: CInt -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall unsafe "__hscore_PrelHandle_write"
write_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
foreign import ccall safe "fdReady"
fdReady :: CInt -> CInt -> CInt -> Bool -> IO CInt
#else /* mingw32_HOST_OS.... */
readRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBuffer loc fd is_stream buf off len
| threaded = blockingReadRawBuffer loc fd is_stream buf off len
| otherwise = asyncReadRawBuffer loc fd is_stream buf off len
readRawBufferPtr :: String -> FD -> Bool -> Ptr CChar -> Int -> CInt -> IO CInt
readRawBufferPtr loc fd is_stream buf off len
| threaded = blockingReadRawBufferPtr loc fd is_stream buf off len
| otherwise = asyncReadRawBufferPtr loc fd is_stream buf off len
writeRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
writeRawBuffer loc fd is_stream buf off len
| threaded = blockingWriteRawBuffer loc fd is_stream buf off len
| otherwise = asyncWriteRawBuffer loc fd is_stream buf off len
writeRawBufferPtr :: String -> FD -> Bool -> Ptr CChar -> Int -> CInt -> IO CInt
writeRawBufferPtr loc fd is_stream buf off len
| threaded = blockingWriteRawBufferPtr loc fd is_stream buf off len
| otherwise = asyncWriteRawBufferPtr loc fd is_stream buf off len
readRawBufferNoBlock :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBufferNoBlock = readRawBuffer
asyncReadRawBuffer loc fd is_stream buf off len = do
(l, rc) <- asyncReadBA (fromIntegral fd) (if is_stream then 1 else 0)
(fromIntegral len) off buf
if l == (1)
then
ioError (errnoToIOError loc (Errno (fromIntegral rc)) Nothing Nothing)
else return (fromIntegral l)
asyncReadRawBufferPtr loc fd is_stream buf off len = do
(l, rc) <- asyncRead (fromIntegral fd) (if is_stream then 1 else 0)
(fromIntegral len) (buf `plusPtr` off)
if l == (1)
then
ioError (errnoToIOError loc (Errno (fromIntegral rc)) Nothing Nothing)
else return (fromIntegral l)
asyncWriteRawBuffer loc fd is_stream buf off len = do
(l, rc) <- asyncWriteBA (fromIntegral fd) (if is_stream then 1 else 0)
(fromIntegral len) off buf
if l == (1)
then
ioError (errnoToIOError loc (Errno (fromIntegral rc)) Nothing Nothing)
else return (fromIntegral l)
asyncWriteRawBufferPtr loc fd is_stream buf off len = do
(l, rc) <- asyncWrite (fromIntegral fd) (if is_stream then 1 else 0)
(fromIntegral len) (buf `plusPtr` off)
if l == (1)
then
ioError (errnoToIOError loc (Errno (fromIntegral rc)) Nothing Nothing)
else return (fromIntegral l)
blockingReadRawBuffer loc fd True buf off len =
throwErrnoIfMinus1Retry loc $
safe_recv_rawBuffer fd buf off len
blockingReadRawBuffer loc fd False buf off len =
throwErrnoIfMinus1Retry loc $
safe_read_rawBuffer fd buf off len
blockingReadRawBufferPtr loc fd True buf off len =
throwErrnoIfMinus1Retry loc $
safe_recv_off fd buf off len
blockingReadRawBufferPtr loc fd False buf off len =
throwErrnoIfMinus1Retry loc $
safe_read_off fd buf off len
blockingWriteRawBuffer loc fd True buf off len =
throwErrnoIfMinus1Retry loc $
safe_send_rawBuffer fd buf off len
blockingWriteRawBuffer loc fd False buf off len =
throwErrnoIfMinus1Retry loc $
safe_write_rawBuffer fd buf off len
blockingWriteRawBufferPtr loc fd True buf off len =
throwErrnoIfMinus1Retry loc $
safe_send_off fd buf off len
blockingWriteRawBufferPtr loc fd False buf off len =
throwErrnoIfMinus1Retry loc $
safe_write_off fd buf off len
foreign import ccall safe "__hscore_PrelHandle_recv"
safe_recv_rawBuffer :: CInt -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_recv"
safe_recv_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_send"
safe_send_rawBuffer :: CInt -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_send"
safe_send_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
#endif
foreign import ccall "rtsSupportsBoundThreads" threaded :: Bool
foreign import ccall safe "__hscore_PrelHandle_read"
safe_read_rawBuffer :: FD -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_read"
safe_read_off :: FD -> Ptr CChar -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_write"
safe_write_rawBuffer :: CInt -> RawBuffer -> Int -> CInt -> IO CInt
foreign import ccall safe "__hscore_PrelHandle_write"
safe_write_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
fd_stdin = 0 :: FD
fd_stdout = 1 :: FD
fd_stderr = 2 :: FD
stdin :: Handle
stdin = unsafePerformIO $ do
(buf, bmode) <- getBuffer fd_stdin ReadBuffer
mkStdHandle fd_stdin "<stdin>" ReadHandle buf bmode
stdout :: Handle
stdout = unsafePerformIO $ do
(buf, bmode) <- getBuffer fd_stdout WriteBuffer
mkStdHandle fd_stdout "<stdout>" WriteHandle buf bmode
stderr :: Handle
stderr = unsafePerformIO $ do
buf <- mkUnBuffer
mkStdHandle fd_stderr "<stderr>" WriteHandle buf NoBuffering
addFilePathToIOError fun fp (IOError h iot _ str _)
= IOError h iot fun str (Just fp)
openFile :: FilePath -> IOMode -> IO Handle
openFile fp im =
catch
(openFile' fp im dEFAULT_OPEN_IN_BINARY_MODE)
(\e -> ioError (addFilePathToIOError "openFile" fp e))
openBinaryFile :: FilePath -> IOMode -> IO Handle
openBinaryFile fp m =
catch
(openFile' fp m True)
(\e -> ioError (addFilePathToIOError "openBinaryFile" fp e))
openFile' filepath mode binary =
withCString filepath $ \ f ->
let
oflags1 = case mode of
ReadMode -> read_flags
#ifdef mingw32_HOST_OS
WriteMode -> write_flags .|. o_TRUNC
#else
WriteMode -> write_flags
#endif
ReadWriteMode -> rw_flags
AppendMode -> append_flags
binary_flags
| binary = o_BINARY
| otherwise = 0
oflags = oflags1 .|. binary_flags
in do
fd <- throwErrnoIfMinus1Retry "openFile"
(c_open f (fromIntegral oflags) 0o666)
stat@(fd_type,_,_) <- fdStat fd
h <- fdToHandle_stat fd (Just stat) False filepath mode binary
`catchException` \e -> do c_close fd; throw e
#ifndef mingw32_HOST_OS
if mode == WriteMode && fd_type == RegularFile
then throwErrnoIf (/=0) "openFile"
(c_ftruncate fd 0)
else return 0
#endif
return h
std_flags = o_NONBLOCK .|. o_NOCTTY
output_flags = std_flags .|. o_CREAT
read_flags = std_flags .|. o_RDONLY
write_flags = output_flags .|. o_WRONLY
rw_flags = output_flags .|. o_RDWR
append_flags = write_flags .|. o_APPEND
fdToHandle_stat :: FD
-> Maybe (FDType, CDev, CIno)
-> Bool
-> FilePath
-> IOMode
-> Bool
-> IO Handle
fdToHandle_stat fd mb_stat is_socket filepath mode binary = do
setNonBlockingFD fd
#ifdef mingw32_HOST_OS
let is_stream = is_socket
#else
let is_stream = True
#endif
let (ha_type, write) =
case mode of
ReadMode -> ( ReadHandle, False )
WriteMode -> ( WriteHandle, True )
ReadWriteMode -> ( ReadWriteHandle, True )
AppendMode -> ( AppendHandle, True )
(fd_type,dev,ino) <-
case mb_stat of
Just x -> return x
Nothing -> fdStat fd
case fd_type of
Directory ->
ioException (IOError Nothing InappropriateType "openFile"
"is a directory" Nothing)
RegularFile -> do
#ifndef mingw32_HOST_OS
r <- lockFile fd dev ino (fromBool write)
when (r == 1) $
ioException (IOError Nothing ResourceBusy "openFile"
"file is locked" Nothing)
#endif
mkFileHandle fd is_stream filepath ha_type binary
Stream
| ReadWriteHandle <- ha_type ->
mkDuplexHandle fd is_stream filepath binary
| otherwise ->
mkFileHandle fd is_stream filepath ha_type binary
RawDevice ->
mkFileHandle fd is_stream filepath ha_type binary
fdToHandle' :: FD -> Maybe FDType -> Bool -> FilePath -> IOMode -> Bool
-> IO Handle
fdToHandle' fd mb_type is_socket filepath mode binary
= do
let mb_stat = case mb_type of
Nothing -> Nothing
Just RegularFile -> Nothing
Just other -> Just (other,0,0)
fdToHandle_stat fd mb_stat is_socket filepath mode binary
fdToHandle :: FD -> IO Handle
fdToHandle fd = do
mode <- fdGetMode fd
let fd_str = "<file descriptor: " ++ show fd ++ ">"
fdToHandle_stat fd Nothing False fd_str mode True
#ifndef mingw32_HOST_OS
foreign import ccall unsafe "lockFile"
lockFile :: CInt -> CDev -> CIno -> CInt -> IO CInt
foreign import ccall unsafe "unlockFile"
unlockFile :: CInt -> IO CInt
#endif
mkStdHandle :: FD -> FilePath -> HandleType -> IORef Buffer -> BufferMode
-> IO Handle
mkStdHandle fd filepath ha_type buf bmode = do
spares <- newIORef BufferListNil
newFileHandle filepath (stdHandleFinalizer filepath)
(Handle__ { haFD = fd,
haType = ha_type,
haIsBin = dEFAULT_OPEN_IN_BINARY_MODE,
haIsStream = False,
haBufferMode = bmode,
haBuffer = buf,
haBuffers = spares,
haOtherSide = Nothing
})
mkFileHandle :: FD -> Bool -> FilePath -> HandleType -> Bool -> IO Handle
mkFileHandle fd is_stream filepath ha_type binary = do
(buf, bmode) <- getBuffer fd (initBufferState ha_type)
#ifdef mingw32_HOST_OS
bmode <- case ha_type of
ReadWriteHandle | not binary -> return NoBuffering
_other -> return bmode
#endif
spares <- newIORef BufferListNil
newFileHandle filepath (handleFinalizer filepath)
(Handle__ { haFD = fd,
haType = ha_type,
haIsBin = binary,
haIsStream = is_stream,
haBufferMode = bmode,
haBuffer = buf,
haBuffers = spares,
haOtherSide = Nothing
})
mkDuplexHandle :: FD -> Bool -> FilePath -> Bool -> IO Handle
mkDuplexHandle fd is_stream filepath binary = do
(w_buf, w_bmode) <- getBuffer fd WriteBuffer
w_spares <- newIORef BufferListNil
let w_handle_ =
Handle__ { haFD = fd,
haType = WriteHandle,
haIsBin = binary,
haIsStream = is_stream,
haBufferMode = w_bmode,
haBuffer = w_buf,
haBuffers = w_spares,
haOtherSide = Nothing
}
write_side <- newMVar w_handle_
(r_buf, r_bmode) <- getBuffer fd ReadBuffer
r_spares <- newIORef BufferListNil
let r_handle_ =
Handle__ { haFD = fd,
haType = ReadHandle,
haIsBin = binary,
haIsStream = is_stream,
haBufferMode = r_bmode,
haBuffer = r_buf,
haBuffers = r_spares,
haOtherSide = Just write_side
}
read_side <- newMVar r_handle_
addMVarFinalizer write_side (handleFinalizer filepath write_side)
return (DuplexHandle filepath read_side write_side)
initBufferState ReadHandle = ReadBuffer
initBufferState _ = WriteBuffer
hClose :: Handle -> IO ()
hClose h@(FileHandle _ m) = do
mb_exc <- hClose' h m
case mb_exc of
Nothing -> return ()
Just e -> throwIO e
hClose h@(DuplexHandle _ r w) = do
mb_exc1 <- hClose' h w
mb_exc2 <- hClose' h r
case (do mb_exc1; mb_exc2) of
Nothing -> return ()
Just e -> throwIO e
hClose' h m = withHandle' "hClose" h m $ hClose_help
hClose_help :: Handle__ -> IO (Handle__, Maybe Exception)
hClose_help handle_ =
case haType handle_ of
ClosedHandle -> return (handle_,Nothing)
_ -> do flushWriteBufferOnly handle_
hClose_handle_ handle_
hClose_handle_ handle_ = do
let fd = haFD handle_
maybe_exception <-
case haOtherSide handle_ of
Nothing -> (do
throwErrnoIfMinus1Retry_ "hClose"
#ifdef mingw32_HOST_OS
(closeFd (haIsStream handle_) fd)
#else
(c_close fd)
#endif
return Nothing
)
`catchException` \e -> return (Just e)
Just _ -> return Nothing
writeIORef (haBuffers handle_) BufferListNil
writeIORef (haBuffer handle_) noBuffer
#ifndef mingw32_HOST_OS
unlockFile fd
#endif
return (handle_{ haFD = 1,
haType = ClosedHandle
},
maybe_exception)
noBuffer = unsafePerformIO $ allocateBuffer 1 ReadBuffer
hFileSize :: Handle -> IO Integer
hFileSize handle =
withHandle_ "hFileSize" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
_ -> do flushWriteBufferOnly handle_
r <- fdFileSize (haFD handle_)
if r /= 1
then return r
else ioException (IOError Nothing InappropriateType "hFileSize"
"not a regular file" Nothing)
hSetFileSize :: Handle -> Integer -> IO ()
hSetFileSize handle size =
withHandle_ "hSetFileSize" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
_ -> do flushWriteBufferOnly handle_
throwErrnoIf (/=0) "hSetFileSize"
(c_ftruncate (haFD handle_) (fromIntegral size))
return ()
hIsEOF :: Handle -> IO Bool
hIsEOF handle =
catch
(do hLookAhead handle; return False)
(\e -> if isEOFError e then return True else ioError e)
isEOF :: IO Bool
isEOF = hIsEOF stdin
hLookAhead :: Handle -> IO Char
hLookAhead handle = do
wantReadableHandle "hLookAhead" handle $ \handle_ -> do
let ref = haBuffer handle_
fd = haFD handle_
is_line = haBufferMode handle_ == LineBuffering
buf <- readIORef ref
new_buf <- if bufferEmpty buf
then fillReadBuffer fd True (haIsStream handle_) buf
else return buf
writeIORef ref new_buf
(c,_) <- readCharFromBuffer (bufBuf buf) (bufRPtr buf)
return c
hSetBuffering :: Handle -> BufferMode -> IO ()
hSetBuffering handle mode =
withAllHandles__ "hSetBuffering" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
_ -> do
flushBuffer handle_
let state = initBufferState (haType handle_)
new_buf <-
case mode of
NoBuffering -> allocateBuffer 1 ReadBuffer
LineBuffering -> allocateBuffer dEFAULT_BUFFER_SIZE state
BlockBuffering Nothing -> allocateBuffer dEFAULT_BUFFER_SIZE state
BlockBuffering (Just n) | n <= 0 -> ioe_bufsiz n
| otherwise -> allocateBuffer n state
writeIORef (haBuffer handle_) new_buf
is_tty <- fdIsTTY (haFD handle_)
when (is_tty && isReadableHandleType (haType handle_)) $
case mode of
#ifndef mingw32_HOST_OS
NoBuffering -> setCooked (haFD handle_) False
#else
NoBuffering -> return ()
#endif
_ -> setCooked (haFD handle_) True
writeIORef (haBuffers handle_) BufferListNil
return (handle_{ haBufferMode = mode })
hFlush :: Handle -> IO ()
hFlush handle =
wantWritableHandle "hFlush" handle $ \ handle_ -> do
buf <- readIORef (haBuffer handle_)
if bufferIsWritable buf && not (bufferEmpty buf)
then do flushed_buf <- flushWriteBuffer (haFD handle_) (haIsStream handle_) buf
writeIORef (haBuffer handle_) flushed_buf
else return ()
data HandlePosn = HandlePosn Handle HandlePosition
instance Eq HandlePosn where
(HandlePosn h1 p1) == (HandlePosn h2 p2) = p1==p2 && h1==h2
instance Show HandlePosn where
showsPrec p (HandlePosn h pos) =
showsPrec p h . showString " at position " . shows pos
type HandlePosition = Integer
hGetPosn :: Handle -> IO HandlePosn
hGetPosn handle = do
posn <- hTell handle
return (HandlePosn handle posn)
hSetPosn :: HandlePosn -> IO ()
hSetPosn (HandlePosn h i) = hSeek h AbsoluteSeek i
data SeekMode
= AbsoluteSeek
| RelativeSeek
| SeekFromEnd
deriving (Eq, Ord, Ix, Enum, Read, Show)
hSeek :: Handle -> SeekMode -> Integer -> IO ()
hSeek handle mode offset =
wantSeekableHandle "hSeek" handle $ \ handle_ -> do
# ifdef DEBUG_DUMP
puts ("hSeek " ++ show (mode,offset) ++ "\n")
# endif
let ref = haBuffer handle_
buf <- readIORef ref
let r = bufRPtr buf
w = bufWPtr buf
fd = haFD handle_
let do_seek =
throwErrnoIfMinus1Retry_ "hSeek"
(c_lseek (haFD handle_) (fromIntegral offset) whence)
whence :: CInt
whence = case mode of
AbsoluteSeek -> sEEK_SET
RelativeSeek -> sEEK_CUR
SeekFromEnd -> sEEK_END
if bufferIsWritable buf
then do new_buf <- flushWriteBuffer fd (haIsStream handle_) buf
writeIORef ref new_buf
do_seek
else do
if mode == RelativeSeek && offset >= 0 && offset < fromIntegral (w r)
then writeIORef ref buf{ bufRPtr = r + fromIntegral offset }
else do
new_buf <- flushReadBuffer (haFD handle_) buf
writeIORef ref new_buf
do_seek
hTell :: Handle -> IO Integer
hTell handle =
wantSeekableHandle "hGetPosn" handle $ \ handle_ -> do
#if defined(mingw32_HOST_OS)
flushBuffer handle_
#endif
let fd = haFD handle_
posn <- fromIntegral `liftM`
throwErrnoIfMinus1Retry "hGetPosn"
(c_lseek fd 0 sEEK_CUR)
let ref = haBuffer handle_
buf <- readIORef ref
let real_posn
| bufferIsWritable buf = posn + fromIntegral (bufWPtr buf)
| otherwise = posn fromIntegral (bufWPtr buf bufRPtr buf)
# ifdef DEBUG_DUMP
puts ("\nhGetPosn: (fd, posn, real_posn) = " ++ show (fd, posn, real_posn) ++ "\n")
puts (" (bufWPtr, bufRPtr) = " ++ show (bufWPtr buf, bufRPtr buf) ++ "\n")
# endif
return real_posn
hIsOpen :: Handle -> IO Bool
hIsOpen handle =
withHandle_ "hIsOpen" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> return False
SemiClosedHandle -> return False
_ -> return True
hIsClosed :: Handle -> IO Bool
hIsClosed handle =
withHandle_ "hIsClosed" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> return True
_ -> return False
hIsReadable :: Handle -> IO Bool
hIsReadable (DuplexHandle _ _ _) = return True
hIsReadable handle =
withHandle_ "hIsReadable" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
htype -> return (isReadableHandleType htype)
hIsWritable :: Handle -> IO Bool
hIsWritable (DuplexHandle _ _ _) = return True
hIsWritable handle =
withHandle_ "hIsWritable" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
htype -> return (isWritableHandleType htype)
hGetBuffering :: Handle -> IO BufferMode
hGetBuffering handle =
withHandle_ "hGetBuffering" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
_ ->
return (haBufferMode handle_)
hIsSeekable :: Handle -> IO Bool
hIsSeekable handle =
withHandle_ "hIsSeekable" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
SemiClosedHandle -> ioe_closedHandle
AppendHandle -> return False
_ -> do t <- fdType (haFD handle_)
return ((t == RegularFile || t == RawDevice)
&& (haIsBin handle_ || tEXT_MODE_SEEK_ALLOWED))
hSetEcho :: Handle -> Bool -> IO ()
hSetEcho handle on = do
isT <- hIsTerminalDevice handle
if not isT
then return ()
else
withHandle_ "hSetEcho" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
_ -> setEcho (haFD handle_) on
hGetEcho :: Handle -> IO Bool
hGetEcho handle = do
isT <- hIsTerminalDevice handle
if not isT
then return False
else
withHandle_ "hGetEcho" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
_ -> getEcho (haFD handle_)
hIsTerminalDevice :: Handle -> IO Bool
hIsTerminalDevice handle = do
withHandle_ "hIsTerminalDevice" handle $ \ handle_ -> do
case haType handle_ of
ClosedHandle -> ioe_closedHandle
_ -> fdIsTTY (haFD handle_)
hSetBinaryMode :: Handle -> Bool -> IO ()
hSetBinaryMode handle bin =
withAllHandles__ "hSetBinaryMode" handle $ \ handle_ ->
do throwErrnoIfMinus1_ "hSetBinaryMode"
(setmode (haFD handle_) bin)
return handle_{haIsBin=bin}
foreign import ccall unsafe "__hscore_setmode"
setmode :: CInt -> Bool -> IO CInt
hDuplicate :: Handle -> IO Handle
hDuplicate h@(FileHandle path m) = do
new_h_ <- withHandle' "hDuplicate" h m (dupHandle h Nothing)
newFileHandle path (handleFinalizer path) new_h_
hDuplicate h@(DuplexHandle path r w) = do
new_w_ <- withHandle' "hDuplicate" h w (dupHandle h Nothing)
new_w <- newMVar new_w_
new_r_ <- withHandle' "hDuplicate" h r (dupHandle h (Just new_w))
new_r <- newMVar new_r_
addMVarFinalizer new_w (handleFinalizer path new_w)
return (DuplexHandle path new_r new_w)
dupHandle :: Handle -> Maybe (MVar Handle__) -> Handle__
-> IO (Handle__, Handle__)
dupHandle h other_side h_ = do
flushBuffer h_
new_fd <- case other_side of
Nothing -> throwErrnoIfMinus1 "dupHandle" $ c_dup (haFD h_)
Just r -> withHandle_' "dupHandle" h r (return . haFD)
dupHandle_ other_side h_ new_fd
dupHandleTo other_side hto_ h_ = do
flushBuffer h_
throwErrnoIfMinus1 "dupHandleTo" $
c_dup2 (haFD h_) (haFD hto_)
dupHandle_ other_side h_ (haFD hto_)
dupHandle_ :: Maybe (MVar Handle__) -> Handle__ -> FD
-> IO (Handle__, Handle__)
dupHandle_ other_side h_ new_fd = do
buffer <- allocateBuffer dEFAULT_BUFFER_SIZE (initBufferState (haType h_))
ioref <- newIORef buffer
ioref_buffers <- newIORef BufferListNil
let new_handle_ = h_{ haFD = new_fd,
haBuffer = ioref,
haBuffers = ioref_buffers,
haOtherSide = other_side }
return (h_, new_handle_)
hDuplicateTo :: Handle -> Handle -> IO ()
hDuplicateTo h1@(FileHandle _ m1) h2@(FileHandle _ m2) = do
withHandle__' "hDuplicateTo" h2 m2 $ \h2_ -> do
_ <- hClose_help h2_
withHandle' "hDuplicateTo" h1 m1 (dupHandleTo Nothing h2_)
hDuplicateTo h1@(DuplexHandle _ r1 w1) h2@(DuplexHandle _ r2 w2) = do
withHandle__' "hDuplicateTo" h2 w2 $ \w2_ -> do
_ <- hClose_help w2_
withHandle' "hDuplicateTo" h1 r1 (dupHandleTo Nothing w2_)
withHandle__' "hDuplicateTo" h2 r2 $ \r2_ -> do
_ <- hClose_help r2_
withHandle' "hDuplicateTo" h1 r1 (dupHandleTo (Just w1) r2_)
hDuplicateTo h1 _ =
ioException (IOError (Just h1) IllegalOperation "hDuplicateTo"
"handles are incompatible" Nothing)
hShow :: Handle -> IO String
hShow h@(FileHandle path _) = showHandle' path False h
hShow h@(DuplexHandle path _ _) = showHandle' path True h
showHandle' filepath is_duplex h =
withHandle_ "showHandle" h $ \hdl_ ->
let
showType | is_duplex = showString "duplex (read-write)"
| otherwise = shows (haType hdl_)
in
return
(( showChar '{' .
showHdl (haType hdl_)
(showString "loc=" . showString filepath . showChar ',' .
showString "type=" . showType . showChar ',' .
showString "binary=" . shows (haIsBin hdl_) . showChar ',' .
showString "buffering=" . showBufMode (unsafePerformIO (readIORef (haBuffer hdl_))) (haBufferMode hdl_) . showString "}" )
) "")
where
showHdl :: HandleType -> ShowS -> ShowS
showHdl ht cont =
case ht of
ClosedHandle -> shows ht . showString "}"
_ -> cont
showBufMode :: Buffer -> BufferMode -> ShowS
showBufMode buf bmo =
case bmo of
NoBuffering -> showString "none"
LineBuffering -> showString "line"
BlockBuffering (Just n) -> showString "block " . showParen True (shows n)
BlockBuffering Nothing -> showString "block " . showParen True (shows def)
where
def :: Int
def = bufSize buf
#if defined(DEBUG_DUMP)
puts :: String -> IO ()
puts s = do write_rawBuffer 1 (unsafeCoerce# (packCString# s)) 0 (fromIntegral (length s))
return ()
#endif
throwErrnoIfMinus1RetryOnBlock :: String -> IO CInt -> IO CInt -> IO CInt
throwErrnoIfMinus1RetryOnBlock loc f on_block =
do
res <- f
if (res :: CInt) == 1
then do
err <- getErrno
if err == eINTR
then throwErrnoIfMinus1RetryOnBlock loc f on_block
else if err == eWOULDBLOCK || err == eAGAIN
then do on_block
else throwErrno loc
else return res
foreign import ccall unsafe "__hscore_supportsTextMode"
tEXT_MODE_SEEK_ALLOWED :: Bool
foreign import ccall unsafe "__hscore_bufsiz" dEFAULT_BUFFER_SIZE :: Int
foreign import ccall unsafe "__hscore_seek_cur" sEEK_CUR :: CInt
foreign import ccall unsafe "__hscore_seek_set" sEEK_SET :: CInt
foreign import ccall unsafe "__hscore_seek_end" sEEK_END :: CInt