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