{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude
, RecordWildCards
, BangPatterns
, NondecreasingIndentation
, RankNTypes
#-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.IO.Handle.Internals (
withHandle, withHandle', withHandle_,
withHandle__', withHandle_', withAllHandles__,
wantWritableHandle, wantReadableHandle, wantReadableHandle_,
wantSeekableHandle,
mkHandle, mkFileHandle, mkDuplexHandle,
openTextEncoding, closeTextCodecs, initBufferState,
dEFAULT_CHAR_BUFFER_SIZE,
flushBuffer, flushWriteBuffer, flushCharReadBuffer,
flushCharBuffer, flushByteReadBuffer, flushByteWriteBuffer,
readTextDevice, writeCharBuffer, readTextDeviceNonBlocking,
decodeByteBuf,
augmentIOError,
ioe_closedHandle, ioe_semiclosedHandle,
ioe_EOF, ioe_notReadable, ioe_notWritable,
ioe_finalizedHandle, ioe_bufsiz,
hClose_help, hLookAhead_,
HandleFinalizer, handleFinalizer,
debugIO,
) where
import GHC.IO
import GHC.IO.IOMode
import GHC.IO.Encoding as Encoding
import GHC.IO.Encoding.Types (CodeBuffer)
import GHC.IO.Handle.Types
import GHC.IO.Buffer
import GHC.IO.BufferedIO (BufferedIO)
import GHC.IO.Exception
import GHC.IO.Device (IODevice, SeekMode(..))
import qualified GHC.IO.Device as IODevice
import qualified GHC.IO.BufferedIO as Buffered
import GHC.Conc.Sync
import GHC.Real
import GHC.Base
import GHC.Exception
import GHC.Num ( Num(..) )
import GHC.Show
import GHC.IORef
import GHC.MVar
import Data.Typeable
import Data.Maybe
import Foreign
import System.Posix.Internals hiding (FD)
import Foreign.C
c_DEBUG_DUMP :: Bool
c_DEBUG_DUMP :: Bool
c_DEBUG_DUMP = Bool
False
type HandleFinalizer = FilePath -> MVar Handle__ -> IO ()
newFileHandle :: FilePath -> Maybe HandleFinalizer -> Handle__ -> IO Handle
newFileHandle :: FilePath -> Maybe HandleFinalizer -> Handle__ -> IO Handle
newFileHandle FilePath
filepath Maybe HandleFinalizer
mb_finalizer Handle__
hc = do
MVar Handle__
m <- Handle__ -> IO (MVar Handle__)
forall a. a -> IO (MVar a)
newMVar Handle__
hc
case Maybe HandleFinalizer
mb_finalizer of
Just HandleFinalizer
finalizer -> MVar Handle__ -> IO () -> IO ()
forall a. MVar a -> IO () -> IO ()
addMVarFinalizer MVar Handle__
m (HandleFinalizer
finalizer FilePath
filepath MVar Handle__
m)
Maybe HandleFinalizer
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> MVar Handle__ -> Handle
FileHandle FilePath
filepath MVar Handle__
m)
{-# INLINE withHandle #-}
withHandle :: String -> Handle -> (Handle__ -> IO (Handle__,a)) -> IO a
withHandle :: FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
withHandle FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO (Handle__, a)
act = FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
forall a.
FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
withHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO (Handle__, a)
act
withHandle FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
m MVar Handle__
_) Handle__ -> IO (Handle__, a)
act = FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
forall a.
FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
withHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO (Handle__, a)
act
withHandle' :: String -> Handle -> MVar Handle__
-> (Handle__ -> IO (Handle__,a)) -> IO a
withHandle' :: FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
withHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO (Handle__, a)
act =
IO a -> IO a
forall a. IO a -> IO a
mask_ (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
(Handle__
h',a
v) <- FilePath
-> Handle
-> (Handle__ -> IO (Handle__, a))
-> MVar Handle__
-> IO (Handle__, a)
forall a.
FilePath -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
do_operation FilePath
fun Handle
h Handle__ -> IO (Handle__, a)
act MVar Handle__
m
Handle__ -> IO ()
checkHandleInvariants Handle__
h'
MVar Handle__ -> Handle__ -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar Handle__
m Handle__
h'
a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
v
{-# INLINE withHandle_ #-}
withHandle_ :: String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ :: FilePath -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO a
act = FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
withHandle_ FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
m MVar Handle__
_) Handle__ -> IO a
act = FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
withHandle_' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' :: FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act = FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
forall a.
FilePath
-> Handle
-> MVar Handle__
-> (Handle__ -> IO (Handle__, a))
-> IO a
withHandle' FilePath
fun Handle
h MVar Handle__
m ((Handle__ -> IO (Handle__, a)) -> IO a)
-> (Handle__ -> IO (Handle__, a)) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle__
h_ -> do
a
a <- Handle__ -> IO a
act Handle__
h_
(Handle__, a) -> IO (Handle__, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__
h_,a
a)
withAllHandles__ :: String -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ :: FilePath -> Handle -> (Handle__ -> IO Handle__) -> IO ()
withAllHandles__ FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO Handle__
act = FilePath
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO Handle__
act
withAllHandles__ FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
r MVar Handle__
w) Handle__ -> IO Handle__
act = do
FilePath
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' FilePath
fun Handle
h MVar Handle__
r Handle__ -> IO Handle__
act
FilePath
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' FilePath
fun Handle
h MVar Handle__
w Handle__ -> IO Handle__
act
withHandle__' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__)
-> IO ()
withHandle__' :: FilePath
-> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO ()
withHandle__' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO Handle__
act =
IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Handle__
h' <- FilePath
-> Handle
-> (Handle__ -> IO Handle__)
-> MVar Handle__
-> IO Handle__
forall a.
FilePath -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
do_operation FilePath
fun Handle
h Handle__ -> IO Handle__
act MVar Handle__
m
Handle__ -> IO ()
checkHandleInvariants Handle__
h'
MVar Handle__ -> Handle__ -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar Handle__
m Handle__
h'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
do_operation :: String -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
do_operation :: FilePath -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
do_operation FilePath
fun Handle
h Handle__ -> IO a
act MVar Handle__
m = do
Handle__
h_ <- MVar Handle__ -> IO Handle__
forall a. MVar a -> IO a
takeMVar MVar Handle__
m
Handle__ -> IO ()
checkHandleInvariants Handle__
h_
Handle__ -> IO a
act Handle__
h_ IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catchException` Handle__ -> SomeException -> IO a
handler Handle__
h_
where
handler :: Handle__ -> SomeException -> IO a
handler Handle__
h_ SomeException
e = do
MVar Handle__ -> Handle__ -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar Handle__
m Handle__
h_
case () of
()
_ | Just IOException
ioe <- SomeException -> Maybe IOException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e ->
IOException -> IO a
forall a. IOException -> IO a
ioError (IOException -> FilePath -> Handle -> IOException
augmentIOError IOException
ioe FilePath
fun Handle
h)
()
_ | Just SomeAsyncException
async_ex <- SomeException -> Maybe SomeAsyncException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e -> do
let SomeAsyncException
_ = SomeAsyncException
async_ex :: SomeAsyncException
ThreadId
t <- IO ThreadId
myThreadId
ThreadId -> SomeException -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ThreadId
t SomeException
e
FilePath -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
forall a.
FilePath -> Handle -> (Handle__ -> IO a) -> MVar Handle__ -> IO a
do_operation FilePath
fun Handle
h Handle__ -> IO a
act MVar Handle__
m
()
_otherwise ->
SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO SomeException
e
augmentIOError :: IOException -> String -> Handle -> IOException
augmentIOError :: IOException -> FilePath -> Handle -> IOException
augmentIOError ioe :: IOException
ioe@IOError{ ioe_filename :: IOException -> Maybe FilePath
ioe_filename = Maybe FilePath
fp } FilePath
fun Handle
h
= IOException
ioe { ioe_handle :: Maybe Handle
ioe_handle = Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
h, ioe_location :: FilePath
ioe_location = FilePath
fun, ioe_filename :: Maybe FilePath
ioe_filename = Maybe FilePath
filepath }
where filepath :: Maybe FilePath
filepath
| Just FilePath
_ <- Maybe FilePath
fp = Maybe FilePath
fp
| Bool
otherwise = case Handle
h of
FileHandle FilePath
path MVar Handle__
_ -> FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path
DuplexHandle FilePath
path MVar Handle__
_ MVar Handle__
_ -> FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path
wantWritableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantWritableHandle :: FilePath -> Handle -> (Handle__ -> IO a) -> IO a
wantWritableHandle FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantWritableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
wantWritableHandle FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
_ MVar Handle__
m) Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantWritableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
wantWritableHandle'
:: String -> Handle -> MVar Handle__
-> (Handle__ -> IO a) -> IO a
wantWritableHandle' :: FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantWritableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m ((Handle__ -> IO a) -> Handle__ -> IO a
forall a. (Handle__ -> IO a) -> Handle__ -> IO a
checkWritableHandle Handle__ -> IO a
act)
checkWritableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkWritableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkWritableHandle Handle__ -> IO a
act 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
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)
haType :: Handle__ -> HandleType
haDevice :: ()
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
..}
= case HandleType
haType of
HandleType
ClosedHandle -> IO a
forall a. IO a
ioe_closedHandle
HandleType
SemiClosedHandle -> IO a
forall a. IO a
ioe_semiclosedHandle
HandleType
ReadHandle -> IO a
forall a. IO a
ioe_notWritable
HandleType
ReadWriteHandle -> do
Buffer CharBufElem
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isWriteBuffer Buffer CharBufElem
buf)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Handle__ -> IO ()
flushCharReadBuffer Handle__
h_
Handle__ -> IO ()
flushByteReadBuffer Handle__
h_
Buffer CharBufElem
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
buf{ bufState :: BufferState
bufState = BufferState
WriteBuffer }
Buffer Word8
buf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
Buffer Word8
buf' <- dev -> Buffer Word8 -> IO (Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Buffer Word8)
Buffered.emptyWriteBuffer dev
haDevice Buffer Word8
buf
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
buf'
Handle__ -> IO a
act Handle__
h_
HandleType
_other -> Handle__ -> IO a
act Handle__
h_
wantReadableHandle :: String -> Handle -> (Handle__ -> IO (Handle__,a)) -> IO a
wantReadableHandle :: FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
wantReadableHandle FilePath
fun Handle
h Handle__ -> IO (Handle__, a)
act = FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
forall a.
FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
withHandle FilePath
fun Handle
h ((Handle__ -> IO (Handle__, a)) -> Handle__ -> IO (Handle__, a)
forall a. (Handle__ -> IO a) -> Handle__ -> IO a
checkReadableHandle Handle__ -> IO (Handle__, a)
act)
wantReadableHandle_ :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ :: FilePath -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantReadableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
wantReadableHandle_ FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
m MVar Handle__
_) Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantReadableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
wantReadableHandle'
:: String -> Handle -> MVar Handle__
-> (Handle__ -> IO a) -> IO a
wantReadableHandle' :: FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
wantReadableHandle' FilePath
fun Handle
h MVar Handle__
m Handle__ -> IO a
act
= FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m ((Handle__ -> IO a) -> Handle__ -> IO a
forall a. (Handle__ -> IO a) -> Handle__ -> IO a
checkReadableHandle Handle__ -> IO a
act)
checkReadableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkReadableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkReadableHandle Handle__ -> IO a
act 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} =
case HandleType
haType of
HandleType
ClosedHandle -> IO a
forall a. IO a
ioe_closedHandle
HandleType
SemiClosedHandle -> IO a
forall a. IO a
ioe_semiclosedHandle
HandleType
AppendHandle -> IO a
forall a. IO a
ioe_notReadable
HandleType
WriteHandle -> IO a
forall a. IO a
ioe_notReadable
HandleType
ReadWriteHandle -> do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isWriteBuffer Buffer Word8
bbuf) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle__ -> IO ()
flushByteWriteBuffer Handle__
h_
Buffer CharBufElem
cbuf' <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
cbuf'{ bufState :: BufferState
bufState = BufferState
ReadBuffer }
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf{ bufState :: BufferState
bufState = BufferState
ReadBuffer }
Handle__ -> IO a
act Handle__
h_
HandleType
_other -> Handle__ -> IO a
act Handle__
h_
wantSeekableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a
wantSeekableHandle :: FilePath -> Handle -> (Handle__ -> IO a) -> IO a
wantSeekableHandle FilePath
fun h :: Handle
h@(DuplexHandle FilePath
_ MVar Handle__
_ MVar Handle__
_) Handle__ -> IO a
_act =
IOException -> IO a
forall a. IOException -> IO a
ioException (Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
h) IOErrorType
IllegalOperation FilePath
fun
FilePath
"handle is not seekable" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
wantSeekableHandle FilePath
fun h :: Handle
h@(FileHandle FilePath
_ MVar Handle__
m) Handle__ -> IO a
act =
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
forall a.
FilePath -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a
withHandle_' FilePath
fun Handle
h MVar Handle__
m ((Handle__ -> IO a) -> Handle__ -> IO a
forall a. (Handle__ -> IO a) -> Handle__ -> IO a
checkSeekableHandle Handle__ -> IO a
act)
checkSeekableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkSeekableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a
checkSeekableHandle Handle__ -> IO a
act handle_ :: Handle__
handle_@Handle__{haDevice :: ()
haDevice=dev
dev} =
case Handle__ -> HandleType
haType Handle__
handle_ of
HandleType
ClosedHandle -> IO a
forall a. IO a
ioe_closedHandle
HandleType
SemiClosedHandle -> IO a
forall a. IO a
ioe_semiclosedHandle
HandleType
AppendHandle -> IO a
forall a. IO a
ioe_notSeekable
HandleType
_ -> do Bool
b <- dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isSeekable dev
dev
if Bool
b then Handle__ -> IO a
act Handle__
handle_
else IO a
forall a. IO a
ioe_notSeekable
ioe_closedHandle, ioe_semiclosedHandle, ioe_EOF,
ioe_notReadable, ioe_notWritable, ioe_cannotFlushNotSeekable,
ioe_notSeekable :: IO a
ioe_closedHandle :: IO a
ioe_closedHandle = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is closed" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_semiclosedHandle :: IO a
ioe_semiclosedHandle = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is semi-closed" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_EOF :: IO a
ioe_EOF = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
EOF FilePath
"" FilePath
"" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_notReadable :: IO a
ioe_notReadable = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is not open for reading" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_notWritable :: IO a
ioe_notWritable = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is not open for writing" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_notSeekable :: IO a
ioe_notSeekable = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is not seekable" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_cannotFlushNotSeekable :: IO a
ioe_cannotFlushNotSeekable = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"cannot flush the read buffer: underlying device is not seekable"
Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
ioe_finalizedHandle :: FilePath -> Handle__
ioe_finalizedHandle :: FilePath -> Handle__
ioe_finalizedHandle FilePath
fp = IOException -> Handle__
forall a e. Exception e => e -> a
throw
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation FilePath
""
FilePath
"handle is finalized" Maybe CInt
forall a. Maybe a
Nothing (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
fp))
ioe_bufsiz :: Int -> IO a
ioe_bufsiz :: Int -> IO a
ioe_bufsiz Int
n = IOException -> IO a
forall a. IOException -> IO a
ioException
(Maybe Handle
-> IOErrorType
-> FilePath
-> FilePath
-> Maybe CInt
-> Maybe FilePath
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument FilePath
"hSetBuffering"
(FilePath
"illegal buffer size " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> Int -> FilePath -> FilePath
forall a. Show a => Int -> a -> FilePath -> FilePath
showsPrec Int
9 Int
n []) Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
streamEncode :: BufferCodec from to state
-> Buffer from -> Buffer to
-> IO (Buffer from, Buffer to)
streamEncode :: BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode BufferCodec from to state
codec Buffer from
from Buffer to
to = ((CodingProgress, Buffer from, Buffer to)
-> (Buffer from, Buffer to))
-> IO (CodingProgress, Buffer from, Buffer to)
-> IO (Buffer from, Buffer to)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(CodingProgress
_, Buffer from
from', Buffer to
to') -> (Buffer from
from', Buffer to
to')) (IO (CodingProgress, Buffer from, Buffer to)
-> IO (Buffer from, Buffer to))
-> IO (CodingProgress, Buffer from, Buffer to)
-> IO (Buffer from, Buffer to)
forall a b. (a -> b) -> a -> b
$ BufferCodec from to state -> CodeBuffer from to
forall from to state.
BufferCodec from to state -> CodeBuffer from to
recoveringEncode BufferCodec from to state
codec Buffer from
from Buffer to
to
recoveringEncode :: BufferCodec from to state -> CodeBuffer from to
recoveringEncode :: BufferCodec from to state -> CodeBuffer from to
recoveringEncode BufferCodec from to state
codec Buffer from
from Buffer to
to = CodeBuffer from to
go Buffer from
from Buffer to
to
where
go :: CodeBuffer from to
go Buffer from
from Buffer to
to = do
(CodingProgress
why, Buffer from
from', Buffer to
to') <- BufferCodec from to state -> CodeBuffer from to
forall from to state.
BufferCodec from to state -> CodeBuffer from to
encode BufferCodec from to state
codec Buffer from
from Buffer to
to
case CodingProgress
why of
CodingProgress
InvalidSequence | Buffer from -> Int
forall e. Buffer e -> Int
bufL Buffer from
from Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Buffer from -> Int
forall e. Buffer e -> Int
bufL Buffer from
from' -> do
(Buffer from
from', Buffer to
to') <- BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
recover BufferCodec from to state
codec Buffer from
from' Buffer to
to'
CodeBuffer from to
go Buffer from
from' Buffer to
to'
CodingProgress
_ -> (CodingProgress, Buffer from, Buffer to)
-> IO (CodingProgress, Buffer from, Buffer to)
forall (m :: * -> *) a. Monad m => a -> m a
return (CodingProgress
why, Buffer from
from', Buffer to
to')
handleFinalizer :: FilePath -> MVar Handle__ -> IO ()
handleFinalizer :: HandleFinalizer
handleFinalizer FilePath
fp MVar Handle__
m = do
Handle__
handle_ <- MVar Handle__ -> IO Handle__
forall a. MVar a -> IO a
takeMVar MVar Handle__
m
(Handle__
handle_', Maybe SomeException
_) <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
handle_
MVar Handle__ -> Handle__ -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar Handle__
m Handle__
handle_'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
dEFAULT_CHAR_BUFFER_SIZE :: Int
dEFAULT_CHAR_BUFFER_SIZE :: Int
dEFAULT_CHAR_BUFFER_SIZE = Int
2048
getCharBuffer :: IODevice dev => dev -> BufferState
-> IO (IORef CharBuffer, BufferMode)
getCharBuffer :: dev -> BufferState -> IO (IORef (Buffer CharBufElem), BufferMode)
getCharBuffer dev
dev BufferState
state = do
Buffer CharBufElem
buffer <- Int -> BufferState -> IO (Buffer CharBufElem)
newCharBuffer Int
dEFAULT_CHAR_BUFFER_SIZE BufferState
state
IORef (Buffer CharBufElem)
ioref <- Buffer CharBufElem -> IO (IORef (Buffer CharBufElem))
forall a. a -> IO (IORef a)
newIORef Buffer CharBufElem
buffer
Bool
is_tty <- dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isTerminal dev
dev
let buffer_mode :: BufferMode
buffer_mode
| Bool
is_tty = BufferMode
LineBuffering
| Bool
otherwise = Maybe Int -> BufferMode
BlockBuffering Maybe Int
forall a. Maybe a
Nothing
(IORef (Buffer CharBufElem), BufferMode)
-> IO (IORef (Buffer CharBufElem), BufferMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (IORef (Buffer CharBufElem)
ioref, BufferMode
buffer_mode)
mkUnBuffer :: BufferState -> IO (IORef CharBuffer, BufferMode)
mkUnBuffer :: BufferState -> IO (IORef (Buffer CharBufElem), BufferMode)
mkUnBuffer BufferState
state = do
Buffer CharBufElem
buffer <- Int -> BufferState -> IO (Buffer CharBufElem)
newCharBuffer Int
dEFAULT_CHAR_BUFFER_SIZE BufferState
state
IORef (Buffer CharBufElem)
ref <- Buffer CharBufElem -> IO (IORef (Buffer CharBufElem))
forall a. a -> IO (IORef a)
newIORef Buffer CharBufElem
buffer
(IORef (Buffer CharBufElem), BufferMode)
-> IO (IORef (Buffer CharBufElem), BufferMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (IORef (Buffer CharBufElem)
ref, BufferMode
NoBuffering)
flushBuffer :: Handle__ -> IO ()
flushBuffer :: Handle__ -> IO ()
flushBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer CharBufElem
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
case Buffer CharBufElem -> BufferState
forall e. Buffer e -> BufferState
bufState Buffer CharBufElem
buf of
BufferState
ReadBuffer -> do
Handle__ -> IO ()
flushCharReadBuffer Handle__
h_
Handle__ -> IO ()
flushByteReadBuffer Handle__
h_
BufferState
WriteBuffer -> do
Handle__ -> IO ()
flushByteWriteBuffer Handle__
h_
flushCharBuffer :: Handle__ -> IO ()
flushCharBuffer :: Handle__ -> IO ()
flushCharBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer CharBufElem
cbuf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
case Buffer CharBufElem -> BufferState
forall e. Buffer e -> BufferState
bufState Buffer CharBufElem
cbuf of
BufferState
ReadBuffer -> do
Handle__ -> IO ()
flushCharReadBuffer Handle__
h_
BufferState
WriteBuffer ->
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
cbuf)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
FilePath -> IO ()
forall a. HasCallStack => FilePath -> a
error FilePath
"internal IO library error: Char buffer non-empty"
flushWriteBuffer :: Handle__ -> IO ()
flushWriteBuffer :: Handle__ -> IO ()
flushWriteBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer Word8
buf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isWriteBuffer Buffer Word8
buf) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle__ -> IO ()
flushByteWriteBuffer Handle__
h_
flushByteWriteBuffer :: Handle__ -> IO ()
flushByteWriteBuffer :: Handle__ -> IO ()
flushByteWriteBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Buffer Word8
bbuf' <- dev -> Buffer Word8 -> IO (Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Buffer Word8)
Buffered.flushWriteBuffer dev
haDevice Buffer Word8
bbuf
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf'
writeCharBuffer :: Handle__ -> CharBuffer -> IO ()
writeCharBuffer :: Handle__ -> Buffer CharBufElem -> IO ()
writeCharBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} !Buffer CharBufElem
cbuf = do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
FilePath -> IO ()
debugIO (FilePath
"writeCharBuffer: cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf)
(Buffer CharBufElem
cbuf',Buffer Word8
bbuf') <- case Maybe (TextEncoder enc_state)
haEncoder of
Maybe (TextEncoder enc_state)
Nothing -> Buffer CharBufElem
-> Buffer Word8 -> IO (Buffer CharBufElem, Buffer Word8)
latin1_encode Buffer CharBufElem
cbuf Buffer Word8
bbuf
Just TextEncoder enc_state
encoder -> (TextEncoder enc_state
-> Buffer CharBufElem
-> Buffer Word8
-> IO (Buffer CharBufElem, Buffer Word8)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode TextEncoder enc_state
encoder) Buffer CharBufElem
cbuf Buffer Word8
bbuf
FilePath -> IO ()
debugIO (FilePath
"writeCharBuffer after encoding: cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf')
if Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isFullBuffer Buffer Word8
bbuf'
Bool -> Bool -> Bool
|| Bool -> Bool
not (Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
cbuf') Bool -> Bool -> Bool
&& Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
cbuf' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
cbuf
Bool -> Bool -> Bool
|| (case BufferMode
haBufferMode of
BlockBuffering (Just Int
s) -> Buffer Word8 -> Int
forall e. Buffer e -> Int
bufferElems Buffer Word8
bbuf' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
s
BufferMode
NoBuffering -> Bool
True
BufferMode
_other -> Bool
False)
then do
Buffer Word8
bbuf'' <- dev -> Buffer Word8 -> IO (Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Buffer Word8)
Buffered.flushWriteBuffer dev
haDevice Buffer Word8
bbuf'
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf''
else
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf'
if Bool -> Bool
not (Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
cbuf')
then Handle__ -> Buffer CharBufElem -> IO ()
writeCharBuffer Handle__
h_ Buffer CharBufElem
cbuf'
else () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
flushCharReadBuffer :: Handle__ -> IO ()
flushCharReadBuffer :: Handle__ -> IO ()
flushCharReadBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer CharBufElem
cbuf <- 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
cbuf Bool -> Bool -> Bool
|| Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
cbuf then () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return () else do
(dec_state
codec_state, Buffer Word8
bbuf0) <- IORef (dec_state, Buffer Word8) -> IO (dec_state, Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (dec_state, Buffer Word8)
haLastDecode
Buffer CharBufElem
cbuf0 <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
cbuf0{ bufL :: Int
bufL=Int
0, bufR :: Int
bufR=Int
0 }
if Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
cbuf0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf0
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
case Maybe (TextDecoder dec_state)
haDecoder of
Maybe (TextDecoder dec_state)
Nothing -> do
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf0 { bufL :: Int
bufL = Buffer Word8 -> Int
forall e. Buffer e -> Int
bufL Buffer Word8
bbuf0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
cbuf0 }
Just TextDecoder dec_state
decoder -> do
FilePath -> IO ()
debugIO (FilePath
"flushCharReadBuffer re-decode, bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf0 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf0)
TextDecoder dec_state -> dec_state -> IO ()
forall from to state. BufferCodec from to state -> state -> IO ()
setState TextDecoder dec_state
decoder dec_state
codec_state
(Buffer Word8
bbuf1,Buffer CharBufElem
cbuf1) <- (TextDecoder dec_state
-> Buffer Word8
-> Buffer CharBufElem
-> IO (Buffer Word8, Buffer CharBufElem)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode TextDecoder dec_state
decoder) Buffer Word8
bbuf0
Buffer CharBufElem
cbuf0{ bufL :: Int
bufL=Int
0, bufR :: Int
bufR=Int
0, bufSize :: Int
bufSize = Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
cbuf0 }
FilePath -> IO ()
debugIO (FilePath
"finished, bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf1 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf1)
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf1
flushByteReadBuffer :: Handle__ -> IO ()
flushByteReadBuffer :: Handle__ -> IO ()
flushByteReadBuffer 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer Word8
bbuf <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
if Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf then () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return () else do
Bool
seekable <- dev -> IO Bool
forall a. IODevice a => a -> IO Bool
IODevice.isSeekable dev
haDevice
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
seekable) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ()
forall a. IO a
ioe_cannotFlushNotSeekable
let seek :: Int
seek = Int -> Int
forall a. Num a => a -> a
negate (Buffer Word8 -> Int
forall e. Buffer e -> Int
bufR Buffer Word8
bbuf Int -> Int -> Int
forall a. Num a => a -> a -> a
- Buffer Word8 -> Int
forall e. Buffer e -> Int
bufL Buffer Word8
bbuf)
FilePath -> IO ()
debugIO (FilePath
"flushByteReadBuffer: new file offset = " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
seek)
dev -> SeekMode -> Integer -> IO ()
forall a. IODevice a => a -> SeekMode -> Integer -> IO ()
IODevice.seek dev
haDevice SeekMode
RelativeSeek (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
seek)
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf{ bufL :: Int
bufL=Int
0, bufR :: Int
bufR=Int
0 }
mkHandle :: (IODevice dev, BufferedIO dev, Typeable dev) => dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle :: dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle dev
dev FilePath
filepath HandleType
ha_type Bool
buffered Maybe TextEncoding
mb_codec NewlineMode
nl Maybe HandleFinalizer
finalizer Maybe (MVar Handle__)
other_side = do
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_codec HandleType
ha_type ((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
$ \ Maybe (TextEncoder es)
mb_encoder Maybe (TextDecoder ds)
mb_decoder -> do
let buf_state :: BufferState
buf_state = HandleType -> BufferState
initBufferState HandleType
ha_type
Buffer Word8
bbuf <- dev -> BufferState -> IO (Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> BufferState -> IO (Buffer Word8)
Buffered.newBuffer dev
dev BufferState
buf_state
IORef (Buffer Word8)
bbufref <- Buffer Word8 -> IO (IORef (Buffer Word8))
forall a. a -> IO (IORef a)
newIORef Buffer Word8
bbuf
IORef (ds, Buffer Word8)
last_decode <- (ds, Buffer Word8) -> IO (IORef (ds, Buffer Word8))
forall a. a -> IO (IORef a)
newIORef (FilePath -> ds
forall a. FilePath -> a
errorWithoutStackTrace FilePath
"codec_state", Buffer Word8
bbuf)
(IORef (Buffer CharBufElem)
cbufref,BufferMode
bmode) <-
if Bool
buffered then dev -> BufferState -> IO (IORef (Buffer CharBufElem), BufferMode)
forall dev.
IODevice dev =>
dev -> BufferState -> IO (IORef (Buffer CharBufElem), BufferMode)
getCharBuffer dev
dev BufferState
buf_state
else BufferState -> IO (IORef (Buffer CharBufElem), BufferMode)
mkUnBuffer BufferState
buf_state
IORef (BufferList CharBufElem)
spares <- BufferList CharBufElem -> IO (IORef (BufferList CharBufElem))
forall a. a -> IO (IORef a)
newIORef BufferList CharBufElem
forall e. BufferList e
BufferListNil
FilePath -> Maybe HandleFinalizer -> Handle__ -> IO Handle
newFileHandle FilePath
filepath Maybe HandleFinalizer
finalizer
(Handle__ :: 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__ { haDevice :: dev
haDevice = dev
dev,
haType :: HandleType
haType = HandleType
ha_type,
haBufferMode :: BufferMode
haBufferMode = BufferMode
bmode,
haByteBuffer :: IORef (Buffer Word8)
haByteBuffer = IORef (Buffer Word8)
bbufref,
haLastDecode :: IORef (ds, Buffer Word8)
haLastDecode = IORef (ds, Buffer Word8)
last_decode,
haCharBuffer :: IORef (Buffer CharBufElem)
haCharBuffer = IORef (Buffer CharBufElem)
cbufref,
haBuffers :: IORef (BufferList CharBufElem)
haBuffers = IORef (BufferList CharBufElem)
spares,
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_codec,
haInputNL :: Newline
haInputNL = NewlineMode -> Newline
inputNL NewlineMode
nl,
haOutputNL :: Newline
haOutputNL = NewlineMode -> Newline
outputNL NewlineMode
nl,
haOtherSide :: Maybe (MVar Handle__)
haOtherSide = Maybe (MVar Handle__)
other_side
})
mkFileHandle :: (IODevice dev, BufferedIO dev, Typeable dev)
=> dev
-> FilePath
-> IOMode
-> Maybe TextEncoding
-> NewlineMode
-> IO Handle
mkFileHandle :: dev
-> FilePath
-> IOMode
-> Maybe TextEncoding
-> NewlineMode
-> IO Handle
mkFileHandle dev
dev FilePath
filepath IOMode
iomode Maybe TextEncoding
mb_codec NewlineMode
tr_newlines = do
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle dev
dev FilePath
filepath (IOMode -> HandleType
ioModeToHandleType IOMode
iomode) Bool
True Maybe TextEncoding
mb_codec
NewlineMode
tr_newlines
(HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer) Maybe (MVar Handle__)
forall a. Maybe a
Nothing
mkDuplexHandle :: (IODevice dev, BufferedIO dev, Typeable dev) => dev
-> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
mkDuplexHandle :: dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
mkDuplexHandle dev
dev FilePath
filepath Maybe TextEncoding
mb_codec NewlineMode
tr_newlines = do
write_side :: Handle
write_side@(FileHandle FilePath
_ MVar Handle__
write_m) <-
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle dev
dev FilePath
filepath HandleType
WriteHandle Bool
True Maybe TextEncoding
mb_codec
NewlineMode
tr_newlines
(HandleFinalizer -> Maybe HandleFinalizer
forall a. a -> Maybe a
Just HandleFinalizer
handleFinalizer)
Maybe (MVar Handle__)
forall a. Maybe a
Nothing
read_side :: Handle
read_side@(FileHandle FilePath
_ MVar Handle__
read_m) <-
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev
-> FilePath
-> HandleType
-> Bool
-> Maybe TextEncoding
-> NewlineMode
-> Maybe HandleFinalizer
-> Maybe (MVar Handle__)
-> IO Handle
mkHandle dev
dev FilePath
filepath HandleType
ReadHandle Bool
True Maybe TextEncoding
mb_codec
NewlineMode
tr_newlines
Maybe HandleFinalizer
forall a. Maybe a
Nothing
(MVar Handle__ -> Maybe (MVar Handle__)
forall a. a -> Maybe a
Just MVar Handle__
write_m)
Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> MVar Handle__ -> MVar Handle__ -> Handle
DuplexHandle FilePath
filepath MVar Handle__
read_m MVar Handle__
write_m)
ioModeToHandleType :: IOMode -> HandleType
ioModeToHandleType :: IOMode -> HandleType
ioModeToHandleType IOMode
ReadMode = HandleType
ReadHandle
ioModeToHandleType IOMode
WriteMode = HandleType
WriteHandle
ioModeToHandleType IOMode
ReadWriteMode = HandleType
ReadWriteHandle
ioModeToHandleType IOMode
AppendMode = HandleType
AppendHandle
initBufferState :: HandleType -> BufferState
initBufferState :: HandleType -> BufferState
initBufferState HandleType
ReadHandle = BufferState
ReadBuffer
initBufferState HandleType
_ = BufferState
WriteBuffer
openTextEncoding
:: Maybe TextEncoding
-> HandleType
-> (forall es ds . Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a)
-> IO a
openTextEncoding :: Maybe TextEncoding
-> HandleType
-> (forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a)
-> IO a
openTextEncoding Maybe TextEncoding
Nothing HandleType
ha_type forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a
cont = Maybe (TextEncoder Any) -> Maybe (TextDecoder Any) -> IO a
forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a
cont Maybe (TextEncoder Any)
forall a. Maybe a
Nothing Maybe (TextDecoder Any)
forall a. Maybe a
Nothing
openTextEncoding (Just TextEncoding{FilePath
IO (TextEncoder estate)
IO (TextDecoder dstate)
mkTextEncoder :: ()
mkTextDecoder :: ()
textEncodingName :: TextEncoding -> FilePath
mkTextEncoder :: IO (TextEncoder estate)
mkTextDecoder :: IO (TextDecoder dstate)
textEncodingName :: FilePath
..}) HandleType
ha_type forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a
cont = do
Maybe (TextDecoder dstate)
mb_decoder <- if HandleType -> Bool
isReadableHandleType HandleType
ha_type then do
TextDecoder dstate
decoder <- IO (TextDecoder dstate)
mkTextDecoder
Maybe (TextDecoder dstate) -> IO (Maybe (TextDecoder dstate))
forall (m :: * -> *) a. Monad m => a -> m a
return (TextDecoder dstate -> Maybe (TextDecoder dstate)
forall a. a -> Maybe a
Just TextDecoder dstate
decoder)
else
Maybe (TextDecoder dstate) -> IO (Maybe (TextDecoder dstate))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (TextDecoder dstate)
forall a. Maybe a
Nothing
Maybe (TextEncoder estate)
mb_encoder <- if HandleType -> Bool
isWritableHandleType HandleType
ha_type then do
TextEncoder estate
encoder <- IO (TextEncoder estate)
mkTextEncoder
Maybe (TextEncoder estate) -> IO (Maybe (TextEncoder estate))
forall (m :: * -> *) a. Monad m => a -> m a
return (TextEncoder estate -> Maybe (TextEncoder estate)
forall a. a -> Maybe a
Just TextEncoder estate
encoder)
else
Maybe (TextEncoder estate) -> IO (Maybe (TextEncoder estate))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (TextEncoder estate)
forall a. Maybe a
Nothing
Maybe (TextEncoder estate) -> Maybe (TextDecoder dstate) -> IO a
forall es ds.
Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a
cont Maybe (TextEncoder estate)
mb_encoder Maybe (TextDecoder dstate)
mb_decoder
closeTextCodecs :: Handle__ -> IO ()
closeTextCodecs :: Handle__ -> IO ()
closeTextCodecs 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
case Maybe (TextDecoder dec_state)
haDecoder of Maybe (TextDecoder dec_state)
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return (); Just TextDecoder dec_state
d -> TextDecoder dec_state -> IO ()
forall from to state. BufferCodec from to state -> IO ()
Encoding.close TextDecoder dec_state
d
case Maybe (TextEncoder enc_state)
haEncoder of Maybe (TextEncoder enc_state)
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return (); Just TextEncoder enc_state
d -> TextEncoder enc_state -> IO ()
forall from to state. BufferCodec from to state -> IO ()
Encoding.close TextEncoder enc_state
d
hClose_help :: Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help :: Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
handle_ =
case Handle__ -> HandleType
haType Handle__
handle_ of
HandleType
ClosedHandle -> (Handle__, Maybe SomeException)
-> IO (Handle__, Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__
handle_,Maybe SomeException
forall a. Maybe a
Nothing)
HandleType
_ -> do Maybe SomeException
mb_exc1 <- IO () -> IO (Maybe SomeException)
trymaybe (IO () -> IO (Maybe SomeException))
-> IO () -> IO (Maybe SomeException)
forall a b. (a -> b) -> a -> b
$ Handle__ -> IO ()
flushWriteBuffer Handle__
handle_
(Handle__
h_, Maybe SomeException
mb_exc2) <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_handle_ Handle__
handle_
(Handle__, Maybe SomeException)
-> IO (Handle__, Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__
h_, if Maybe SomeException -> Bool
forall a. Maybe a -> Bool
isJust Maybe SomeException
mb_exc1 then Maybe SomeException
mb_exc1 else Maybe SomeException
mb_exc2)
trymaybe :: IO () -> IO (Maybe SomeException)
trymaybe :: IO () -> IO (Maybe SomeException)
trymaybe IO ()
io = (do IO ()
io; Maybe SomeException -> IO (Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SomeException
forall a. Maybe a
Nothing) IO (Maybe SomeException)
-> (SomeException -> IO (Maybe SomeException))
-> IO (Maybe SomeException)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catchException` \SomeException
e -> Maybe SomeException -> IO (Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeException -> Maybe SomeException
forall a. a -> Maybe a
Just SomeException
e)
hClose_handle_ :: Handle__ -> IO (Handle__, Maybe SomeException)
hClose_handle_ :: Handle__ -> IO (Handle__, Maybe SomeException)
hClose_handle_ 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Maybe SomeException
maybe_exception <-
case Maybe (MVar Handle__)
haOtherSide of
Maybe (MVar Handle__)
Nothing -> IO () -> IO (Maybe SomeException)
trymaybe (IO () -> IO (Maybe SomeException))
-> IO () -> IO (Maybe SomeException)
forall a b. (a -> b) -> a -> b
$ dev -> IO ()
forall a. IODevice a => a -> IO ()
IODevice.close dev
haDevice
Just MVar Handle__
_ -> Maybe SomeException -> IO (Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SomeException
forall a. Maybe a
Nothing
IORef (BufferList CharBufElem) -> BufferList CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (BufferList CharBufElem)
haBuffers BufferList CharBufElem
forall e. BufferList e
BufferListNil
IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
noCharBuffer
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
noByteBuffer
Handle__ -> IO ()
closeTextCodecs Handle__
h_
(Handle__, Maybe SomeException)
-> IO (Handle__, Maybe SomeException)
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__ :: 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__{ haType :: HandleType
haType = HandleType
ClosedHandle, 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haDevice :: dev
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haDevice :: dev
.. }, Maybe SomeException
maybe_exception)
{-# NOINLINE noCharBuffer #-}
noCharBuffer :: CharBuffer
noCharBuffer :: Buffer CharBufElem
noCharBuffer = IO (Buffer CharBufElem) -> Buffer CharBufElem
forall a. IO a -> a
unsafePerformIO (IO (Buffer CharBufElem) -> Buffer CharBufElem)
-> IO (Buffer CharBufElem) -> Buffer CharBufElem
forall a b. (a -> b) -> a -> b
$ Int -> BufferState -> IO (Buffer CharBufElem)
newCharBuffer Int
1 BufferState
ReadBuffer
{-# NOINLINE noByteBuffer #-}
noByteBuffer :: Buffer Word8
noByteBuffer :: Buffer Word8
noByteBuffer = IO (Buffer Word8) -> Buffer Word8
forall a. IO a -> a
unsafePerformIO (IO (Buffer Word8) -> Buffer Word8)
-> IO (Buffer Word8) -> Buffer Word8
forall a b. (a -> b) -> a -> b
$ Int -> BufferState -> IO (Buffer Word8)
newByteBuffer Int
1 BufferState
ReadBuffer
hLookAhead_ :: Handle__ -> IO Char
hLookAhead_ :: Handle__ -> IO CharBufElem
hLookAhead_ 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} = do
Buffer CharBufElem
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
Buffer CharBufElem
new_buf <- if Buffer CharBufElem -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer CharBufElem
buf
then Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice Handle__
handle_ Buffer CharBufElem
buf
else Buffer CharBufElem -> IO (Buffer CharBufElem)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer CharBufElem
buf
IORef (Buffer CharBufElem) -> Buffer CharBufElem -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer CharBufElem)
haCharBuffer Buffer CharBufElem
new_buf
RawCharBuffer -> Int -> IO CharBufElem
peekCharBuf (Buffer CharBufElem -> RawCharBuffer
forall e. Buffer e -> RawBuffer e
bufRaw Buffer CharBufElem
buf) (Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufL Buffer CharBufElem
buf)
debugIO :: String -> IO ()
debugIO :: FilePath -> IO ()
debugIO FilePath
s
| Bool
c_DEBUG_DUMP
= do CSsize
_ <- FilePath -> (CStringLen -> IO CSsize) -> IO CSsize
forall a. FilePath -> (CStringLen -> IO a) -> IO a
withCStringLen (FilePath
s FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n") ((CStringLen -> IO CSsize) -> IO CSsize)
-> (CStringLen -> IO CSsize) -> IO CSsize
forall a b. (a -> b) -> a -> b
$
\(Ptr CChar
p, Int
len) -> CInt -> Ptr Word8 -> CSize -> IO CSsize
c_write CInt
1 (Ptr CChar -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
readTextDevice :: Handle__ -> CharBuffer -> IO CharBuffer
readTextDevice :: Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} Buffer CharBufElem
cbuf = do
Buffer Word8
bbuf0 <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
FilePath -> IO ()
debugIO (FilePath
"readTextDevice: cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf0)
Buffer Word8
bbuf1 <- if Bool -> Bool
not (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf0)
then Buffer Word8 -> IO (Buffer Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer Word8
bbuf0
else do
(Int
r,Buffer Word8
bbuf1) <- dev -> Buffer Word8 -> IO (Int, Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Int, Buffer Word8)
Buffered.fillReadBuffer dev
haDevice Buffer Word8
bbuf0
if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then IO (Buffer Word8)
forall a. IO a
ioe_EOF else do
Buffer Word8 -> IO (Buffer Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer Word8
bbuf1
FilePath -> IO ()
debugIO (FilePath
"readTextDevice after reading: bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf1)
(Buffer Word8
bbuf2,Buffer CharBufElem
cbuf') <-
case Maybe (TextDecoder dec_state)
haDecoder of
Maybe (TextDecoder dec_state)
Nothing -> do
IORef (dec_state, Buffer Word8)
-> (dec_state, Buffer Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (dec_state, Buffer Word8)
haLastDecode (FilePath -> dec_state
forall a. FilePath -> a
errorWithoutStackTrace FilePath
"codec_state", Buffer Word8
bbuf1)
Buffer Word8
-> Buffer CharBufElem -> IO (Buffer Word8, Buffer CharBufElem)
latin1_decode Buffer Word8
bbuf1 Buffer CharBufElem
cbuf
Just TextDecoder dec_state
decoder -> do
dec_state
state <- TextDecoder dec_state -> IO dec_state
forall from to state. BufferCodec from to state -> IO state
getState TextDecoder dec_state
decoder
IORef (dec_state, Buffer Word8)
-> (dec_state, Buffer Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (dec_state, Buffer Word8)
haLastDecode (dec_state
state, Buffer Word8
bbuf1)
(TextDecoder dec_state
-> Buffer Word8
-> Buffer CharBufElem
-> IO (Buffer Word8, Buffer CharBufElem)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode TextDecoder dec_state
decoder) Buffer Word8
bbuf1 Buffer CharBufElem
cbuf
FilePath -> IO ()
debugIO (FilePath
"readTextDevice after decoding: cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf2)
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf2
if Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf
then Handle__
-> Buffer Word8 -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice' Handle__
h_ Buffer Word8
bbuf2 Buffer CharBufElem
cbuf
else Buffer CharBufElem -> IO (Buffer CharBufElem)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer CharBufElem
cbuf'
readTextDevice' :: Handle__ -> Buffer Word8 -> CharBuffer -> IO CharBuffer
readTextDevice' :: Handle__
-> Buffer Word8 -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice' 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} Buffer Word8
bbuf0 Buffer CharBufElem
cbuf0 = do
Buffer Word8
bbuf1 <- Buffer Word8 -> IO (Buffer Word8)
slideContents Buffer Word8
bbuf0
let Just TextDecoder dec_state
decoder = Maybe (TextDecoder dec_state)
haDecoder
(Int
r,Buffer Word8
bbuf2) <- dev -> Buffer Word8 -> IO (Int, Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Int, Buffer Word8)
Buffered.fillReadBuffer dev
haDevice Buffer Word8
bbuf1
if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then do
if Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf2 then IO (Buffer CharBufElem)
forall a. IO a
ioe_EOF else do
(Buffer Word8
bbuf3, Buffer CharBufElem
cbuf1) <- TextDecoder dec_state
-> Buffer Word8
-> Buffer CharBufElem
-> IO (Buffer Word8, Buffer CharBufElem)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
recover TextDecoder dec_state
decoder Buffer Word8
bbuf2 Buffer CharBufElem
cbuf0
FilePath -> IO ()
debugIO (FilePath
"readTextDevice' after recovery: bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf3 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
", cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf1)
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf3
if Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf0
then Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice Handle__
h_ Buffer CharBufElem
cbuf1
else Buffer CharBufElem -> IO (Buffer CharBufElem)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer CharBufElem
cbuf1
else do
FilePath -> IO ()
debugIO (FilePath
"readTextDevice' after reading: bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf2)
(Buffer Word8
bbuf3,Buffer CharBufElem
cbuf1) <- do
dec_state
state <- TextDecoder dec_state -> IO dec_state
forall from to state. BufferCodec from to state -> IO state
getState TextDecoder dec_state
decoder
IORef (dec_state, Buffer Word8)
-> (dec_state, Buffer Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (dec_state, Buffer Word8)
haLastDecode (dec_state
state, Buffer Word8
bbuf2)
(TextDecoder dec_state
-> Buffer Word8
-> Buffer CharBufElem
-> IO (Buffer Word8, Buffer CharBufElem)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode TextDecoder dec_state
decoder) Buffer Word8
bbuf2 Buffer CharBufElem
cbuf0
FilePath -> IO ()
debugIO (FilePath
"readTextDevice' after decoding: cbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer CharBufElem -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer CharBufElem
cbuf1 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" bbuf=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Buffer Word8 -> FilePath
forall a. Buffer a -> FilePath
summaryBuffer Buffer Word8
bbuf3)
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf3
if Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Buffer CharBufElem -> Int
forall e. Buffer e -> Int
bufR Buffer CharBufElem
cbuf1
then Handle__
-> Buffer Word8 -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDevice' Handle__
h_ Buffer Word8
bbuf3 Buffer CharBufElem
cbuf1
else Buffer CharBufElem -> IO (Buffer CharBufElem)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer CharBufElem
cbuf1
readTextDeviceNonBlocking :: Handle__ -> CharBuffer -> IO CharBuffer
readTextDeviceNonBlocking :: Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
readTextDeviceNonBlocking 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} Buffer CharBufElem
cbuf = do
Buffer Word8
bbuf0 <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Buffer Word8 -> Bool
forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
bbuf0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
(Maybe Int
r,Buffer Word8
bbuf1) <- dev -> Buffer Word8 -> IO (Maybe Int, Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Maybe Int, Buffer Word8)
Buffered.fillReadBuffer0 dev
haDevice Buffer Word8
bbuf0
if Maybe Int -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Int
r then IO ()
forall a. IO a
ioe_EOF else do
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf1
Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
decodeByteBuf Handle__
h_ Buffer CharBufElem
cbuf
decodeByteBuf :: Handle__ -> CharBuffer -> IO CharBuffer
decodeByteBuf :: Handle__ -> Buffer CharBufElem -> IO (Buffer CharBufElem)
decodeByteBuf 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
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
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)
haType :: Handle__ -> HandleType
haDevice :: ()
..} Buffer CharBufElem
cbuf = do
Buffer Word8
bbuf0 <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
(Buffer Word8
bbuf2,Buffer CharBufElem
cbuf') <-
case Maybe (TextDecoder dec_state)
haDecoder of
Maybe (TextDecoder dec_state)
Nothing -> do
IORef (dec_state, Buffer Word8)
-> (dec_state, Buffer Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (dec_state, Buffer Word8)
haLastDecode (FilePath -> dec_state
forall a. FilePath -> a
errorWithoutStackTrace FilePath
"codec_state", Buffer Word8
bbuf0)
Buffer Word8
-> Buffer CharBufElem -> IO (Buffer Word8, Buffer CharBufElem)
latin1_decode Buffer Word8
bbuf0 Buffer CharBufElem
cbuf
Just TextDecoder dec_state
decoder -> do
dec_state
state <- TextDecoder dec_state -> IO dec_state
forall from to state. BufferCodec from to state -> IO state
getState TextDecoder dec_state
decoder
IORef (dec_state, Buffer Word8)
-> (dec_state, Buffer Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (dec_state, Buffer Word8)
haLastDecode (dec_state
state, Buffer Word8
bbuf0)
(TextDecoder dec_state
-> Buffer Word8
-> Buffer CharBufElem
-> IO (Buffer Word8, Buffer CharBufElem)
forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
streamEncode TextDecoder dec_state
decoder) Buffer Word8
bbuf0 Buffer CharBufElem
cbuf
IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
bbuf2
Buffer CharBufElem -> IO (Buffer CharBufElem)
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer CharBufElem
cbuf'