{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, RecordWildCards
, NondecreasingIndentation
#-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
module GHC.IO.Handle (
Handle,
BufferMode(..),
mkFileHandle, mkDuplexHandle,
hFileSize, hSetFileSize, hIsEOF, isEOF, hLookAhead,
hSetBuffering, hSetBinaryMode, hSetEncoding, hGetEncoding,
hFlush, hFlushAll, hDuplicate, hDuplicateTo,
hClose, hClose_help,
LockMode(..), hLock, hTryLock,
HandlePosition, HandlePosn(..), hGetPosn, hSetPosn,
SeekMode(..), hSeek, hTell,
hIsOpen, hIsClosed, hIsReadable, hIsWritable, hGetBuffering, hIsSeekable,
hSetEcho, hGetEcho, hIsTerminalDevice,
hSetNewlineMode, Newline(..), NewlineMode(..), nativeNewline,
noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
hShow,
hWaitForInput, hGetChar, hGetLine, hGetContents, hPutChar, hPutStr,
hGetBuf, hGetBufNonBlocking, hPutBuf, hPutBufNonBlocking
) where
import GHC.IO
import GHC.IO.Exception
import GHC.IO.Encoding
import GHC.IO.Buffer
import GHC.IO.BufferedIO ( BufferedIO )
import GHC.IO.Device as IODevice
import GHC.IO.Handle.FD
import GHC.IO.Handle.Lock
import GHC.IO.Handle.Types
import GHC.IO.Handle.Internals
import GHC.IO.Handle.Text
import qualified GHC.IO.BufferedIO as Buffered
import GHC.Base
import GHC.Exception
import GHC.MVar
import GHC.IORef
import GHC.Show
import GHC.Num
import GHC.Real
import Data.Maybe
import Data.Typeable
hClose :: Handle -> IO ()
hClose :: Handle -> IO ()
hClose h :: Handle
h@(FileHandle _ m :: MVar Handle__
m) = do
Maybe SomeException
mb_exc <- Handle -> MVar Handle__ -> IO (Maybe SomeException)
hClose' Handle
h MVar Handle__
m
Maybe SomeException -> Handle -> IO ()
hClose_maybethrow Maybe SomeException
mb_exc Handle
h
hClose h :: Handle
h@(DuplexHandle _ r :: MVar Handle__
r w :: MVar Handle__
w) = do
[Maybe SomeException]
excs <- (MVar Handle__ -> IO (Maybe SomeException))
-> [MVar Handle__] -> IO [Maybe SomeException]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Handle -> MVar Handle__ -> IO (Maybe SomeException)
hClose' Handle
h) [MVar Handle__
r,MVar Handle__
w]
Maybe SomeException -> Handle -> IO ()
hClose_maybethrow ([SomeException] -> Maybe SomeException
forall a. [a] -> Maybe a
listToMaybe ([Maybe SomeException] -> [SomeException]
forall a. [Maybe a] -> [a]
catMaybes [Maybe SomeException]
excs)) Handle
h
hClose_maybethrow :: Maybe SomeException -> Handle -> IO ()
hClose_maybethrow :: Maybe SomeException -> Handle -> IO ()
hClose_maybethrow Nothing h :: Handle
h = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
hClose_maybethrow (Just e :: SomeException
e) h :: Handle
h = SomeException -> Handle -> IO ()
hClose_rethrow SomeException
e Handle
h
hClose_rethrow :: SomeException -> Handle -> IO ()
hClose_rethrow :: SomeException -> Handle -> IO ()
hClose_rethrow e :: SomeException
e h :: Handle
h =
case SomeException -> Maybe IOException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just ioe :: IOException
ioe -> IOException -> IO ()
forall a. IOException -> IO a
ioError (IOException -> String -> Handle -> IOException
augmentIOError IOException
ioe "hClose" Handle
h)
Nothing -> SomeException -> IO ()
forall e a. Exception e => e -> IO a
throwIO SomeException
e
hClose' :: Handle -> MVar Handle__ -> IO (Maybe SomeException)
hClose' :: Handle -> MVar Handle__ -> IO (Maybe SomeException)
hClose' h :: Handle
h m :: MVar Handle__
m = String
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, Maybe SomeException))
-> IO (Maybe SomeException)
forall a.
String
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
withHandle' "hClose" Handle
h MVar Handle__
m ((Handle__ -> IO (Handle__, Maybe SomeException))
-> IO (Maybe SomeException))
-> (Handle__ -> IO (Handle__, Maybe SomeException))
-> IO (Maybe SomeException)
forall a b. (a -> b) -> a -> b
$ Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help
hFileSize :: Handle -> IO Integer
hFileSize :: Handle -> IO Integer
hFileSize handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Integer) -> IO Integer
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hFileSize" Handle
handle ((Handle__ -> IO Integer) -> IO Integer)
-> (Handle__ -> IO Integer) -> IO Integer
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{haDevice :: ()
haDevice=dev
dev} -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> IO Integer
forall a. IO a
ioe_closedHandle
SemiClosedHandle -> IO Integer
forall a. IO a
ioe_semiclosedHandle
_ -> do Handle__ -> IO ()
flushWriteBuffer Handle__
handle_
Integer
r <- dev -> IO Integer
forall a. IODevice a => a -> IO Integer
IODevice.getSize dev
dev
if Integer
r Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
/= -1
then Integer -> IO Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
r
else IOException -> IO Integer
forall a. IOException -> IO a
ioException (Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InappropriateType "hFileSize"
"not a regular file" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
hSetFileSize :: Handle -> Integer -> IO ()
hSetFileSize :: Handle -> Integer -> IO ()
hSetFileSize handle :: Handle
handle size :: Integer
size =
String -> Handle -> (Handle__ -> IO ()) -> IO ()
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hSetFileSize" Handle
handle ((Handle__ -> IO ()) -> IO ()) -> (Handle__ -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{haDevice :: ()
haDevice=dev
dev} -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> IO ()
forall a. IO a
ioe_closedHandle
SemiClosedHandle -> IO ()
forall a. IO a
ioe_semiclosedHandle
_ -> do Handle__ -> IO ()
flushWriteBuffer Handle__
handle_
dev -> Integer -> IO ()
forall a. IODevice a => a -> Integer -> IO ()
IODevice.setSize dev
dev Integer
size
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
hIsEOF :: Handle -> IO Bool
hIsEOF :: Handle -> IO Bool
hIsEOF handle :: Handle
handle = String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ "hIsEOF" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Handle__{..} -> do
Buffer CharBufElem
cbuf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
if Bool -> Bool
not (Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
cbuf) then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False else do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
if Bool -> Bool
not (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf) then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False else do
(r :: Int
r,bbuf' :: Buffer Word8
bbuf') <- dev -> Buffer Word8 -> IO (Int, Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Int, Buffer Word8)
Buffered.fillReadBuffer dev
haDevice Buffer Word8
bbuf
if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0
then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else do IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
isEOF :: IO Bool
isEOF :: IO Bool
isEOF = Handle -> IO Bool
hIsEOF Handle
stdin
hLookAhead :: Handle -> IO Char
hLookAhead :: Handle -> IO CharBufElem
hLookAhead handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO CharBufElem) -> IO CharBufElem
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ "hLookAhead" Handle
handle Handle__ -> IO CharBufElem
hLookAhead_
hSetBuffering :: Handle -> BufferMode -> IO ()
hSetBuffering :: Handle -> BufferMode -> IO ()
hSetBuffering handle :: Handle
handle mode :: BufferMode
mode =
String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ "hSetBuffering" Handle
handle ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{..} -> do
case HandleType
haType of
ClosedHandle -> IO Handle__
forall a. IO a
ioe_closedHandle
_ -> do
if BufferMode
mode BufferMode -> BufferMode -> Bool
forall a. Eq a => a -> a -> Bool
== BufferMode
haBufferMode then Handle__ -> IO Handle__
forall (m :: * -> *) a. Monad m => a -> m a
return Handle__
handle_ else do
case BufferMode
mode of
BlockBuffering (Just n :: Int
n) | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 -> Int -> IO ()
forall a. Int -> IO a
ioe_bufsiz Int
n
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Bool
is_tty <- dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isTerminal dev
haDevice
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
is_tty Bool -> Bool -> Bool
&& HandleType -> Bool
isReadableHandleType HandleType
haType) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
case BufferMode
mode of
#if !defined(mingw32_HOST_OS)
NoBuffering -> dev -> Bool -> IO ()
forall a. IODevice a => a -> Bool -> IO ()
IODevice.setRaw dev
haDevice Bool
True
#else
NoBuffering -> return ()
#endif
_ -> dev -> Bool -> IO ()
forall a. IODevice a => a -> Bool -> IO ()
IODevice.setRaw dev
haDevice Bool
False
IORef (BufferList CharBufElem) -> BufferList CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (BufferList CharBufElem)
haBuffers BufferList CharBufElem
forall e. BufferList e
BufferListNil
Handle__ -> IO Handle__
forall (m :: * -> *) a. Monad m => a -> m a
return $WHandle__ :: forall dev enc_state dec_state.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> HandleType
-> IORef (Buffer Word8)
-> BufferMode
-> IORef (dec_state, Buffer Word8)
-> IORef (Buffer CharBufElem)
-> IORef (BufferList CharBufElem)
-> Maybe (TextEncoder enc_state)
-> Maybe (TextDecoder dec_state)
-> Maybe TextEncoding
-> Newline
-> Newline
-> Maybe (MVar Handle__)
-> Handle__
Handle__{ haBufferMode :: BufferMode
haBufferMode = BufferMode
mode,.. }
hSetEncoding :: Handle -> TextEncoding -> IO ()
hSetEncoding :: Handle -> TextEncoding -> IO ()
hSetEncoding hdl :: Handle
hdl encoding :: TextEncoding
encoding = do
String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ "hSetEncoding" Handle
hdl ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_@Handle__{..} -> do
Handle__ -> IO ()
flushCharBuffer Handle__
h_
Handle__ -> IO ()
closeTextCodecs Handle__
h_
Maybe TextEncoding
-> HandleType
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__
forall a.
Maybe TextEncoding
-> HandleType
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a)
-> IO a
openTextEncoding (TextEncoding -> Maybe TextEncoding
forall a. a -> Maybe a
Just TextEncoding
encoding) HandleType
haType ((forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__)
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__
forall a b. (a -> b) -> a -> b
$ \ mb_encoder :: Maybe (TextEncoder es)
mb_encoder mb_decoder :: Maybe (TextDecoder ds)
mb_decoder -> do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
IORef (ds, Buffer Word8)
ref <- (ds, Buffer Word8) -> IO (IORef (ds, Buffer Word8))
forall a. a -> IO (IORef a)
newIORef (String -> (ds, Buffer Word8)
forall a. String -> a
errorWithoutStackTrace "last_decode")
Handle__ -> IO Handle__
forall (m :: * -> *) a. Monad m => a -> m a
return ($WHandle__ :: forall dev enc_state dec_state.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> HandleType
-> IORef (Buffer Word8)
-> BufferMode
-> IORef (dec_state, Buffer Word8)
-> IORef (Buffer CharBufElem)
-> IORef (BufferList CharBufElem)
-> Maybe (TextEncoder enc_state)
-> Maybe (TextDecoder dec_state)
-> Maybe TextEncoding
-> Newline
-> Newline
-> Maybe (MVar Handle__)
-> Handle__
Handle__{ haLastDecode :: IORef (ds, Buffer Word8)
haLastDecode = IORef (ds, Buffer Word8)
ref,
haDecoder :: Maybe (TextDecoder ds)
haDecoder = Maybe (TextDecoder ds)
mb_decoder,
haEncoder :: Maybe (TextEncoder es)
haEncoder = Maybe (TextEncoder es)
mb_encoder,
haCodec :: Maybe TextEncoding
haCodec = TextEncoding -> Maybe TextEncoding
forall a. a -> Maybe a
Just TextEncoding
encoding, .. })
hGetEncoding :: Handle -> IO (Maybe TextEncoding)
hGetEncoding :: Handle -> IO (Maybe TextEncoding)
hGetEncoding hdl :: Handle
hdl =
String
-> Handle
-> (Handle__ -> IO (Maybe TextEncoding))
-> IO (Maybe TextEncoding)
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hGetEncoding" Handle
hdl ((Handle__ -> IO (Maybe TextEncoding)) -> IO (Maybe TextEncoding))
-> (Handle__ -> IO (Maybe TextEncoding)) -> IO (Maybe TextEncoding)
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_@Handle__{..} -> Maybe TextEncoding -> IO (Maybe TextEncoding)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextEncoding
haCodec
hFlush :: Handle -> IO ()
hFlush :: Handle -> IO ()
hFlush handle :: Handle
handle = String -> Handle -> (Handle__ -> IO ()) -> IO ()
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantWritableHandle "hFlush" Handle
handle Handle__ -> IO ()
flushWriteBuffer
hFlushAll :: Handle -> IO ()
hFlushAll :: Handle -> IO ()
hFlushAll handle :: Handle
handle = String -> Handle -> (Handle__ -> IO ()) -> IO ()
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hFlushAll" Handle
handle Handle__ -> IO ()
flushBuffer
data HandlePosn = HandlePosn Handle HandlePosition
instance Eq HandlePosn where
(HandlePosn h1 :: Handle
h1 p1 :: Integer
p1) == :: HandlePosn -> HandlePosn -> Bool
== (HandlePosn h2 :: Handle
h2 p2 :: Integer
p2) = Integer
p1Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==Integer
p2 Bool -> Bool -> Bool
&& Handle
h1Handle -> Handle -> Bool
forall a. Eq a => a -> a -> Bool
==Handle
h2
instance Show HandlePosn where
showsPrec :: Int -> HandlePosn -> ShowS
showsPrec p :: Int
p (HandlePosn h :: Handle
h pos :: Integer
pos) =
Int -> Handle -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Handle
h ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString " at position " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ShowS
forall a. Show a => a -> ShowS
shows Integer
pos
type HandlePosition = Integer
hGetPosn :: Handle -> IO HandlePosn
hGetPosn :: Handle -> IO HandlePosn
hGetPosn handle :: Handle
handle = do
Integer
posn <- Handle -> IO Integer
hTell Handle
handle
HandlePosn -> IO HandlePosn
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle -> Integer -> HandlePosn
HandlePosn Handle
handle Integer
posn)
hSetPosn :: HandlePosn -> IO ()
hSetPosn :: HandlePosn -> IO ()
hSetPosn (HandlePosn h :: Handle
h i :: Integer
i) = Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
i
hSeek :: Handle -> SeekMode -> Integer -> IO ()
hSeek :: Handle -> SeekMode -> Integer -> IO ()
hSeek handle :: Handle
handle mode :: SeekMode
mode offset :: Integer
offset =
String -> Handle -> (Handle__ -> IO ()) -> IO ()
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantSeekableHandle "hSeek" Handle
handle ((Handle__ -> IO ()) -> IO ()) -> (Handle__ -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{..} -> do
String -> IO ()
debugIO ("hSeek " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (SeekMode, Integer) -> String
forall a. Show a => a -> String
show (SeekMode
mode,Integer
offset))
Buffer CharBufElem
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
if Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isWriteBuffer Buffer CharBufElem
buf
then do Handle__ -> IO ()
flushWriteBuffer Handle__
handle_
dev -> SeekMode -> Integer -> IO ()
forall a. IODevice a => a -> SeekMode -> Integer -> IO ()
IODevice.seek dev
haDevice SeekMode
mode Integer
offset
else do
let r :: Int
r = Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
buf; w :: Int
w = Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
buf
if SeekMode
mode SeekMode -> SeekMode -> Bool
forall a. Eq a => a -> a -> Bool
== SeekMode
RelativeSeek Bool -> Bool -> Bool
&& Maybe (TextDecoder dec_state) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (TextDecoder dec_state)
haDecoder Bool -> Bool -> Bool
&&
Integer
offset Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 Bool -> Bool -> Bool
&& Integer
offset Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
r)
then IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
buf{ bufL :: Int
bufL = Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
offset }
else do
Handle__ -> IO ()
flushCharReadBuffer Handle__
handle_
Handle__ -> IO ()
flushByteReadBuffer Handle__
handle_
dev -> SeekMode -> Integer -> IO ()
forall a. IODevice a => a -> SeekMode -> Integer -> IO ()
IODevice.seek dev
haDevice SeekMode
mode Integer
offset
hTell :: Handle -> IO Integer
hTell :: Handle -> IO Integer
hTell handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Integer) -> IO Integer
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantSeekableHandle "hGetPosn" Handle
handle ((Handle__ -> IO Integer) -> IO Integer)
-> (Handle__ -> IO Integer) -> IO Integer
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{..} -> do
Integer
posn <- dev -> IO Integer
forall a. IODevice a => a -> IO Integer
IODevice.tell dev
haDevice
Handle__ -> IO ()
flushCharBuffer Handle__
handle_
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
let real_posn :: Integer
real_posn
| Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isWriteBuffer Buffer Word8
bbuf = Integer
posn Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Buffer Word8 -> Int
forall e. Buffer e -> Int
bufferElems Buffer Word8
bbuf)
| Bool
otherwise = Integer
posn Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Buffer Word8 -> Int
forall e. Buffer e -> Int
bufferElems Buffer Word8
bbuf)
Buffer CharBufElem
cbuf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
String -> IO ()
debugIO ("\nhGetPosn: (posn, real_posn) = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Integer, Integer) -> String
forall a. Show a => a -> String
show (Integer
posn, Integer
real_posn))
String -> IO ()
debugIO (" cbuf: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> String
forall a. Buffer a -> String
summaryBuffer Buffer CharBufElem
cbuf String -> ShowS
forall a. [a] -> [a] -> [a]
++
" bbuf: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> String
forall a. Buffer a -> String
summaryBuffer Buffer Word8
bbuf)
Integer -> IO Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
real_posn
hIsOpen :: Handle -> IO Bool
hIsOpen :: Handle -> IO Bool
hIsOpen handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsOpen" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_ -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
SemiClosedHandle -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
_ -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
hIsClosed :: Handle -> IO Bool
hIsClosed :: Handle -> IO Bool
hIsClosed handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsClosed" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_ -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
_ -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
hIsReadable :: Handle -> IO Bool
hIsReadable :: Handle -> IO Bool
hIsReadable (DuplexHandle _ _ _) = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
hIsReadable handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsReadable" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_ -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> IO Bool
forall a. IO a
ioe_closedHandle
SemiClosedHandle -> IO Bool
forall a. IO a
ioe_semiclosedHandle
htype :: HandleType
htype -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (HandleType -> Bool
isReadableHandleType HandleType
htype)
hIsWritable :: Handle -> IO Bool
hIsWritable :: Handle -> IO Bool
hIsWritable (DuplexHandle _ _ _) = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
hIsWritable handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsWritable" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_ -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> IO Bool
forall a. IO a
ioe_closedHandle
SemiClosedHandle -> IO Bool
forall a. IO a
ioe_semiclosedHandle
htype :: HandleType
htype -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (HandleType -> Bool
isWritableHandleType HandleType
htype)
hGetBuffering :: Handle -> IO BufferMode
hGetBuffering :: Handle -> IO BufferMode
hGetBuffering handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO BufferMode) -> IO BufferMode
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hGetBuffering" Handle
handle ((Handle__ -> IO BufferMode) -> IO BufferMode)
-> (Handle__ -> IO BufferMode) -> IO BufferMode
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_ -> do
case Handle__ -> HandleType
haType Handle__
handle_ of
ClosedHandle -> IO BufferMode
forall a. IO a
ioe_closedHandle
_ ->
BufferMode -> IO BufferMode
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__ -> BufferMode
haBufferMode Handle__
handle_)
hIsSeekable :: Handle -> IO Bool
hIsSeekable :: Handle -> IO Bool
hIsSeekable handle :: Handle
handle =
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsSeekable" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ handle_ :: Handle__
handle_@Handle__{..} -> do
case HandleType
haType of
ClosedHandle -> IO Bool
forall a. IO a
ioe_closedHandle
SemiClosedHandle -> IO Bool
forall a. IO a
ioe_semiclosedHandle
AppendHandle -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
_ -> dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isSeekable dev
haDevice
hSetEcho :: Handle -> Bool -> IO ()
hSetEcho :: Handle -> Bool -> IO ()
hSetEcho handle :: Handle
handle on :: Bool
on = do
Bool
isT <- Handle -> IO Bool
hIsTerminalDevice Handle
handle
if Bool -> Bool
not Bool
isT
then () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else
String -> Handle -> (Handle__ -> IO ()) -> IO ()
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hSetEcho" Handle
handle ((Handle__ -> IO ()) -> IO ()) -> (Handle__ -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle__{..} -> do
case HandleType
haType of
ClosedHandle -> IO ()
forall a. IO a
ioe_closedHandle
_ -> dev -> Bool -> IO ()
forall a. IODevice a => a -> Bool -> IO ()
IODevice.setEcho dev
haDevice Bool
on
hGetEcho :: Handle -> IO Bool
hGetEcho :: Handle -> IO Bool
hGetEcho handle :: Handle
handle = do
Bool
isT <- Handle -> IO Bool
hIsTerminalDevice Handle
handle
if Bool -> Bool
not Bool
isT
then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hGetEcho" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Handle__{..} -> do
case HandleType
haType of
ClosedHandle -> IO Bool
forall a. IO a
ioe_closedHandle
_ -> dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.getEcho dev
haDevice
hIsTerminalDevice :: Handle -> IO Bool
hIsTerminalDevice :: Handle -> IO Bool
hIsTerminalDevice handle :: Handle
handle = do
String -> Handle -> (Handle__ -> IO Bool) -> IO Bool
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "hIsTerminalDevice" Handle
handle ((Handle__ -> IO Bool) -> IO Bool)
-> (Handle__ -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Handle__{..} -> do
case HandleType
haType of
ClosedHandle -> IO Bool
forall a. IO a
ioe_closedHandle
_ -> dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isTerminal dev
haDevice
hSetBinaryMode :: Handle -> Bool -> IO ()
hSetBinaryMode :: Handle -> Bool -> IO ()
hSetBinaryMode handle :: Handle
handle bin :: Bool
bin =
String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ "hSetBinaryMode" Handle
handle ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ h_ :: Handle__
h_@Handle__{..} ->
do
Handle__ -> IO ()
flushCharBuffer Handle__
h_
Handle__ -> IO ()
closeTextCodecs Handle__
h_
Maybe TextEncoding
mb_te <- if Bool
bin then Maybe TextEncoding -> IO (Maybe TextEncoding)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextEncoding
forall a. Maybe a
Nothing
else (TextEncoding -> Maybe TextEncoding)
-> IO TextEncoding -> IO (Maybe TextEncoding)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TextEncoding -> Maybe TextEncoding
forall a. a -> Maybe a
Just IO TextEncoding
getLocaleEncoding
Maybe TextEncoding
-> HandleType
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__
forall a.
Maybe TextEncoding
-> HandleType
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a)
-> IO a
openTextEncoding Maybe TextEncoding
mb_te HandleType
haType ((forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__)
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO Handle__)
-> IO Handle__
forall a b. (a -> b) -> a -> b
$ \ mb_encoder :: Maybe (TextEncoder es)
mb_encoder mb_decoder :: Maybe (TextDecoder ds)
mb_decoder -> do
let nl :: NewlineMode
nl | Bool
bin = NewlineMode
noNewlineTranslation
| Bool
otherwise = NewlineMode
nativeNewlineMode
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
IORef (ds, Buffer Word8)
ref <- (ds, Buffer Word8) -> IO (IORef (ds, Buffer Word8))
forall a. a -> IO (IORef a)
newIORef (String -> ds
forall a. String -> a
errorWithoutStackTrace "codec_state", Buffer Word8
bbuf)
Handle__ -> IO Handle__
forall (m :: * -> *) a. Monad m => a -> m a
return $WHandle__ :: forall dev enc_state dec_state.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> HandleType
-> IORef (Buffer Word8)
-> BufferMode
-> IORef (dec_state, Buffer Word8)
-> IORef (Buffer CharBufElem)
-> IORef (BufferList CharBufElem)
-> Maybe (TextEncoder enc_state)
-> Maybe (TextDecoder dec_state)
-> Maybe TextEncoding
-> Newline
-> Newline
-> Maybe (MVar Handle__)
-> Handle__
Handle__{ haLastDecode :: IORef (ds, Buffer Word8)
haLastDecode = IORef (ds, Buffer Word8)
ref,
haEncoder :: Maybe (TextEncoder es)
haEncoder = Maybe (TextEncoder es)
mb_encoder,
haDecoder :: Maybe (TextDecoder ds)
haDecoder = Maybe (TextDecoder ds)
mb_decoder,
haCodec :: Maybe TextEncoding
haCodec = Maybe TextEncoding
mb_te,
haInputNL :: Newline
haInputNL = NewlineMode -> Newline
inputNL NewlineMode
nl,
haOutputNL :: Newline
haOutputNL = NewlineMode -> Newline
outputNL NewlineMode
nl, .. }
hSetNewlineMode :: Handle -> NewlineMode -> IO ()
hSetNewlineMode :: Handle -> NewlineMode -> IO ()
hSetNewlineMode handle :: Handle
handle NewlineMode{ inputNL :: NewlineMode -> Newline
inputNL=Newline
i, outputNL :: NewlineMode -> Newline
outputNL=Newline
o } =
String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ "hSetNewlineMode" Handle
handle ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_@Handle__{..} ->
do
Handle__ -> IO ()
flushBuffer Handle__
h_
Handle__ -> IO Handle__
forall (m :: * -> *) a. Monad m => a -> m a
return Handle__
h_{ haInputNL :: Newline
haInputNL=Newline
i, haOutputNL :: Newline
haOutputNL=Newline
o }
hDuplicate :: Handle -> IO Handle
hDuplicate :: Handle -> IO Handle
hDuplicate h :: Handle
h@(FileHandle path :: String
path m :: MVar Handle__
m) = do
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle) -> IO Handle
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicate" Handle
h MVar Handle__
m ((Handle__ -> IO Handle) -> IO Handle)
-> (Handle__ -> IO Handle) -> IO Handle
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_ ->
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle String
path Handle
h Maybe (MVar Handle__)
forall a. Maybe a
Nothing Handle__
h_ (HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer)
hDuplicate h :: Handle
h@(DuplexHandle path :: String
path r :: MVar Handle__
r w :: MVar Handle__
w) = do
write_side :: Handle
write_side@(FileHandle _ write_m :: MVar Handle__
write_m) <-
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle) -> IO Handle
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicate" Handle
h MVar Handle__
w ((Handle__ -> IO Handle) -> IO Handle)
-> (Handle__ -> IO Handle) -> IO Handle
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_ ->
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle String
path Handle
h Maybe (MVar Handle__)
forall a. Maybe a
Nothing Handle__
h_ (HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer)
read_side :: Handle
read_side@(FileHandle _ read_m :: MVar Handle__
read_m) <-
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle) -> IO Handle
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicate" Handle
h MVar Handle__
r ((Handle__ -> IO Handle) -> IO Handle)
-> (Handle__ -> IO Handle) -> IO Handle
forall a b. (a -> b) -> a -> b
$ \h_ :: Handle__
h_ ->
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle String
path Handle
h (MVar Handle__ -> Maybe (MVar Handle__)
forall a. a -> Maybe a
Just MVar Handle__
write_m) Handle__
h_ Maybe HandleFinalizer
forall a. Maybe a
Nothing
Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> MVar Handle__ -> MVar Handle__ -> Handle
DuplexHandle String
path MVar Handle__
read_m MVar Handle__
write_m)
dupHandle :: FilePath
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle :: String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle filepath :: String
filepath h :: Handle
h other_side :: Maybe (MVar Handle__)
other_side h_ :: Handle__
h_@Handle__{..} mb_finalizer :: Maybe HandleFinalizer
mb_finalizer = do
Handle__ -> IO ()
flushBuffer Handle__
h_
case Maybe (MVar Handle__)
other_side of
Nothing -> do
dev
new_dev <- dev -> IO dev
forall a. IODevice a => a -> IO a
IODevice.dup dev
haDevice
dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ dev
new_dev String
filepath Maybe (MVar Handle__)
other_side Handle__
h_ Maybe HandleFinalizer
mb_finalizer
Just r :: MVar Handle__
r ->
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle) -> IO Handle
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "dupHandle" Handle
h MVar Handle__
r ((Handle__ -> IO Handle) -> IO Handle)
-> (Handle__ -> IO Handle) -> IO Handle
forall a b. (a -> b) -> a -> b
$ \Handle__{haDevice :: ()
haDevice=dev
dev} -> do
dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ dev
dev String
filepath Maybe (MVar Handle__)
other_side Handle__
h_ Maybe HandleFinalizer
mb_finalizer
dupHandle_ :: (IODevice dev, BufferedIO dev, Typeable dev) => dev
-> FilePath
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ :: dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ new_dev :: dev
new_dev filepath :: String
filepath other_side :: Maybe (MVar Handle__)
other_side h_ :: Handle__
h_@Handle__{..} mb_finalizer :: Maybe HandleFinalizer
mb_finalizer = do
Maybe TextEncoding
mb_codec <- if Maybe (TextEncoder enc_state) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (TextEncoder enc_state)
haEncoder then (TextEncoding -> Maybe TextEncoding)
-> IO TextEncoding -> IO (Maybe TextEncoding)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TextEncoding -> Maybe TextEncoding
forall a. a -> Maybe a
Just IO TextEncoding
getLocaleEncoding else Maybe TextEncoding -> IO (Maybe TextEncoding)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextEncoding
forall a. Maybe a
Nothing
dev
-> String
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> String
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle dev
new_dev String
filepath HandleType
haType Bool
True Maybe TextEncoding
mb_codec
NewlineMode :: Newline -> Newline -> NewlineMode
NewlineMode { inputNL :: Newline
inputNL = Newline
haInputNL, outputNL :: Newline
outputNL = Newline
haOutputNL }
Maybe HandleFinalizer
mb_finalizer Maybe (MVar Handle__)
other_side
hDuplicateTo :: Handle -> Handle -> IO ()
hDuplicateTo :: Handle -> Handle -> IO ()
hDuplicateTo h1 :: Handle
h1@(FileHandle path :: String
path m1 :: MVar Handle__
m1) h2 :: Handle
h2@(FileHandle _ m2 :: MVar Handle__
m2) = do
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' "hDuplicateTo" Handle
h2 MVar Handle__
m2 ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \h2_ :: Handle__
h2_ -> do
(Handle__, Maybe SomeException)
_ <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
h2_
String
-> Handle
-> MVar Handle__
-> (Handle__ -> IO Handle__)
-> IO Handle__
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicateTo" Handle
h1 MVar Handle__
m1 ((Handle__ -> IO Handle__) -> IO Handle__)
-> (Handle__ -> IO Handle__) -> IO Handle__
forall a b. (a -> b) -> a -> b
$ \h1_ :: Handle__
h1_ -> do
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo String
path Handle
h1 Maybe (MVar Handle__)
forall a. Maybe a
Nothing Handle__
h2_ Handle__
h1_ (HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer)
hDuplicateTo h1 :: Handle
h1@(DuplexHandle path :: String
path r1 :: MVar Handle__
r1 w1 :: MVar Handle__
w1) h2 :: Handle
h2@(DuplexHandle _ r2 :: MVar Handle__
r2 w2 :: MVar Handle__
w2) = do
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' "hDuplicateTo" Handle
h2 MVar Handle__
w2 ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \w2_ :: Handle__
w2_ -> do
(Handle__, Maybe SomeException)
_ <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
w2_
String
-> Handle
-> MVar Handle__
-> (Handle__ -> IO Handle__)
-> IO Handle__
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicateTo" Handle
h1 MVar Handle__
w1 ((Handle__ -> IO Handle__) -> IO Handle__)
-> (Handle__ -> IO Handle__) -> IO Handle__
forall a b. (a -> b) -> a -> b
$ \w1_ :: Handle__
w1_ -> do
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo String
path Handle
h1 Maybe (MVar Handle__)
forall a. Maybe a
Nothing Handle__
w2_ Handle__
w1_ (HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer)
String
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' "hDuplicateTo" Handle
h2 MVar Handle__
r2 ((Handle__ -> IO Handle__) -> IO ())
-> (Handle__ -> IO Handle__) -> IO ()
forall a b. (a -> b) -> a -> b
$ \r2_ :: Handle__
r2_ -> do
(Handle__, Maybe SomeException)
_ <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
r2_
String
-> Handle
-> MVar Handle__
-> (Handle__ -> IO Handle__)
-> IO Handle__
forall a.
String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' "hDuplicateTo" Handle
h1 MVar Handle__
r1 ((Handle__ -> IO Handle__) -> IO Handle__)
-> (Handle__ -> IO Handle__) -> IO Handle__
forall a b. (a -> b) -> a -> b
$ \r1_ :: Handle__
r1_ -> do
String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo String
path Handle
h1 (MVar Handle__ -> Maybe (MVar Handle__)
forall a. a -> Maybe a
Just MVar Handle__
w1) Handle__
r2_ Handle__
r1_ Maybe HandleFinalizer
forall a. Maybe a
Nothing
hDuplicateTo h1 :: Handle
h1 _ =
Handle -> IO ()
forall a. Handle -> IO a
ioe_dupHandlesNotCompatible Handle
h1
ioe_dupHandlesNotCompatible :: Handle -> IO a
ioe_dupHandlesNotCompatible :: Handle -> IO a
ioe_dupHandlesNotCompatible h :: Handle
h =
IOException -> IO a
forall a. IOException -> IO a
ioException (Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
h) IOErrorType
IllegalOperation "hDuplicateTo"
"handles are incompatible" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
dupHandleTo :: FilePath
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo :: String
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo filepath :: String
filepath h :: Handle
h other_side :: Maybe (MVar Handle__)
other_side
hto_ :: Handle__
hto_@Handle__{haDevice :: ()
haDevice=dev
devTo,..}
h_ :: Handle__
h_@Handle__{haDevice :: ()
haDevice=dev
dev} mb_finalizer :: Maybe HandleFinalizer
mb_finalizer = do
Handle__ -> IO ()
flushBuffer Handle__
h_
case dev -> Maybe dev
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast dev
devTo of
Nothing -> Handle -> IO Handle__
forall a. Handle -> IO a
ioe_dupHandlesNotCompatible Handle
h
Just dev' :: dev
dev' -> do
dev
_ <- dev -> dev -> IO dev
forall a. IODevice a => a -> a -> IO a
IODevice.dup2 dev
dev dev
dev'
FileHandle _ m :: MVar Handle__
m <- dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> String
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ dev
dev' String
filepath Maybe (MVar Handle__)
other_side Handle__
h_ Maybe HandleFinalizer
mb_finalizer
MVar Handle__ -> IO Handle__
forall a. MVar a -> IO a
takeMVar MVar Handle__
m
hShow :: Handle -> IO String
hShow :: Handle -> IO String
hShow h :: Handle
h@(FileHandle path :: String
path _) = String -> Bool -> Handle -> IO String
showHandle' String
path Bool
False Handle
h
hShow h :: Handle
h@(DuplexHandle path :: String
path _ _) = String -> Bool -> Handle -> IO String
showHandle' String
path Bool
True Handle
h
showHandle' :: String -> Bool -> Handle -> IO String
showHandle' :: String -> Bool -> Handle -> IO String
showHandle' filepath :: String
filepath is_duplex :: Bool
is_duplex h :: Handle
h =
String -> Handle -> (Handle__ -> IO String) -> IO String
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ "showHandle" Handle
h ((Handle__ -> IO String) -> IO String)
-> (Handle__ -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \hdl_ :: Handle__
hdl_ ->
let
showType :: ShowS
showType | Bool
is_duplex = String -> ShowS
showString "duplex (read-write)"
| Bool
otherwise = HandleType -> ShowS
forall a. Show a => a -> ShowS
shows (Handle__ -> HandleType
haType Handle__
hdl_)
in
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return
(( CharBufElem -> ShowS
showChar '{' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
HandleType -> ShowS -> ShowS
showHdl (Handle__ -> HandleType
haType Handle__
hdl_)
(String -> ShowS
showString "loc=" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
filepath ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CharBufElem -> ShowS
showChar ',' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString "type=" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
showType ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CharBufElem -> ShowS
showChar ',' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString "buffering=" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Buffer CharBufElem -> BufferMode -> ShowS
forall e. Buffer e -> BufferMode -> ShowS
showBufMode (IO (Buffer CharBufElem) -> Buffer CharBufElem
forall a. IO a -> a
unsafePerformIO (IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef (Handle__ -> IORef (Buffer CharBufElem)
haCharBuffer Handle__
hdl_))) (Handle__ -> BufferMode
haBufferMode Handle__
hdl_) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "}" )
) "")
where
showHdl :: HandleType -> ShowS -> ShowS
showHdl :: HandleType -> ShowS -> ShowS
showHdl ht :: HandleType
ht cont :: ShowS
cont =
case HandleType
ht of
ClosedHandle -> HandleType -> ShowS
forall a. Show a => a -> ShowS
shows HandleType
ht ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "}"
_ -> ShowS
cont
showBufMode :: Buffer e -> BufferMode -> ShowS
showBufMode :: Buffer e -> BufferMode -> ShowS
showBufMode buf :: Buffer e
buf bmo :: BufferMode
bmo =
case BufferMode
bmo of
NoBuffering -> String -> ShowS
showString "none"
LineBuffering -> String -> ShowS
showString "line"
BlockBuffering (Just n :: Int
n) -> String -> ShowS
showString "block " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ShowS -> ShowS
showParen Bool
True (Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
n)
BlockBuffering Nothing -> String -> ShowS
showString "block " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ShowS -> ShowS
showParen Bool
True (Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
def)
where
def :: Int
def :: Int
def = Buffer e -> Int
forall e. Buffer e -> Int
bufSize Buffer e
buf