{-# LANGUAGE BangPatterns, CPP, RecordWildCards #-}
{-# LANGUAGE Trustworthy #-}
module Data.Text.Lazy.IO
(
readFile
, writeFile
, appendFile
, hGetContents
, hGetLine
, hPutStr
, hPutStrLn
, interact
, getContents
, getLine
, putStr
, putStrLn
) where
import Data.Text.Lazy (Text)
import Prelude hiding (appendFile, getContents, getLine, interact,
putStr, putStrLn, readFile, writeFile)
import System.IO (Handle, IOMode(..), openFile, stdin, stdout,
withFile)
import qualified Data.Text.Lazy as L
import qualified Control.Exception as E
import Control.Monad (when)
import Data.IORef (readIORef)
import Data.Text.Internal.IO (hGetLineWith, readChunk, hPutStream)
import Data.Text.Internal.Lazy (chunk, empty)
import Data.Text.Internal.Lazy.Fusion (stream, streamLn)
import GHC.IO.Buffer (isEmptyBuffer)
import GHC.IO.Exception (IOException(..), IOErrorType(..), ioException)
import GHC.IO.Handle.Internals (augmentIOError, hClose_help,
wantReadableHandle, withHandle)
import GHC.IO.Handle.Types (Handle__(..), HandleType(..))
import System.IO (BufferMode(..), hGetBuffering, hSetBuffering)
import System.IO.Error (isEOFError)
import System.IO.Unsafe (unsafeInterleaveIO)
readFile :: FilePath -> IO Text
readFile :: FilePath -> IO Text
readFile FilePath
name = FilePath -> IOMode -> IO Handle
openFile FilePath
name IOMode
ReadMode IO Handle -> (Handle -> IO Text) -> IO Text
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> IO Text
hGetContents
writeFile :: FilePath -> Text -> IO ()
writeFile :: FilePath -> Text -> IO ()
writeFile FilePath
p = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
p IOMode
WriteMode ((Handle -> IO ()) -> IO ())
-> (Text -> Handle -> IO ()) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Handle -> Text -> IO ()) -> Text -> Handle -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Handle -> Text -> IO ()
hPutStr
appendFile :: FilePath -> Text -> IO ()
appendFile :: FilePath -> Text -> IO ()
appendFile FilePath
p = FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
p IOMode
AppendMode ((Handle -> IO ()) -> IO ())
-> (Text -> Handle -> IO ()) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Handle -> Text -> IO ()) -> Text -> Handle -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Handle -> Text -> IO ()
hPutStr
hGetContents :: Handle -> IO Text
hGetContents :: Handle -> IO Text
hGetContents Handle
h = do
Handle -> IO ()
chooseGoodBuffering Handle
h
FilePath -> Handle -> (Handle__ -> IO (Handle__, Text)) -> IO Text
forall a.
FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
wantReadableHandle FilePath
"hGetContents" Handle
h ((Handle__ -> IO (Handle__, Text)) -> IO Text)
-> (Handle__ -> IO (Handle__, Text)) -> IO Text
forall a b. (a -> b) -> a -> b
$ \Handle__
hh -> do
ts <- Handle -> IO Text
lazyRead Handle
h
return (hh{haType=SemiClosedHandle}, ts)
chooseGoodBuffering :: Handle -> IO ()
chooseGoodBuffering :: Handle -> IO ()
chooseGoodBuffering Handle
h = do
bufMode <- Handle -> IO BufferMode
hGetBuffering Handle
h
when (bufMode == BlockBuffering Nothing) $
hSetBuffering h (BlockBuffering (Just 16384))
lazyRead :: Handle -> IO Text
lazyRead :: Handle -> IO Text
lazyRead Handle
h = IO Text -> IO Text
forall a. IO a -> IO a
unsafeInterleaveIO (IO Text -> IO Text) -> IO Text -> IO Text
forall a b. (a -> b) -> a -> b
$
FilePath -> Handle -> (Handle__ -> IO (Handle__, Text)) -> IO Text
forall a.
FilePath -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a
withHandle FilePath
"hGetContents" Handle
h ((Handle__ -> IO (Handle__, Text)) -> IO Text)
-> (Handle__ -> IO (Handle__, Text)) -> IO Text
forall a b. (a -> b) -> a -> b
$ \Handle__
hh -> do
case Handle__ -> HandleType
haType Handle__
hh of
HandleType
ClosedHandle -> (Handle__, Text) -> IO (Handle__, Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle__
hh, Text
L.empty)
HandleType
SemiClosedHandle -> Handle -> Handle__ -> IO (Handle__, Text)
lazyReadBuffered Handle
h Handle__
hh
HandleType
_ -> IOException -> IO (Handle__, Text)
forall a. HasCallStack => 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
"hGetContents"
FilePath
"illegal handle type" Maybe CInt
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing)
lazyReadBuffered :: Handle -> Handle__ -> IO (Handle__, Text)
lazyReadBuffered :: Handle -> Handle__ -> IO (Handle__, Text)
lazyReadBuffered Handle
h hh :: Handle__
hh@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
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)
haDevice :: ()
..} = do
buf <- IORef (Buffer CharBufElem) -> IO (Buffer CharBufElem)
forall a. IORef a -> IO a
readIORef IORef (Buffer CharBufElem)
haCharBuffer
(do t <- readChunk hh buf
ts <- lazyRead h
return (hh, chunk t ts)) `E.catch` \IOException
e -> do
(hh', _) <- Handle__ -> IO (Handle__, Maybe SomeException)
hClose_help Handle__
hh
if isEOFError e
then return $ if isEmptyBuffer buf
then (hh', empty)
else (hh', L.singleton '\r')
else E.throwIO (augmentIOError e "hGetContents" h)
hGetLine :: Handle -> IO Text
hGetLine :: Handle -> IO Text
hGetLine = ([Text] -> Text) -> Handle -> IO Text
forall t. ([Text] -> t) -> Handle -> IO t
hGetLineWith [Text] -> Text
L.fromChunks
hPutStr :: Handle -> Text -> IO ()
hPutStr :: Handle -> Text -> IO ()
hPutStr Handle
h = Handle -> Stream CharBufElem -> IO ()
hPutStream Handle
h (Stream CharBufElem -> IO ())
-> (Text -> Stream CharBufElem) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream CharBufElem
stream
hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn Handle
h = Handle -> Stream CharBufElem -> IO ()
hPutStream Handle
h (Stream CharBufElem -> IO ())
-> (Text -> Stream CharBufElem) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream CharBufElem
streamLn
interact :: (Text -> Text) -> IO ()
interact :: (Text -> Text) -> IO ()
interact Text -> Text
f = Text -> IO ()
putStr (Text -> IO ()) -> (Text -> Text) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
f (Text -> IO ()) -> IO Text -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO Text
getContents
getContents :: IO Text
getContents :: IO Text
getContents = Handle -> IO Text
hGetContents Handle
stdin
getLine :: IO Text
getLine :: IO Text
getLine = Handle -> IO Text
hGetLine Handle
stdin
putStr :: Text -> IO ()
putStr :: Text -> IO ()
putStr = Handle -> Text -> IO ()
hPutStr Handle
stdout
putStrLn :: Text -> IO ()
putStrLn :: Text -> IO ()
putStrLn = Handle -> Text -> IO ()
hPutStrLn Handle
stdout