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(..), hPutChar, openFile, stdin, stdout,
                  withFile)
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as L
#if __GLASGOW_HASKELL__ <= 610
import Data.Text.Lazy.Encoding (decodeUtf8)
import qualified Data.ByteString.Char8 as S8
import qualified Data.ByteString.Lazy.Char8 as L8
#else
import Control.Exception (throw)
import Control.Monad (when)
import Data.IORef (readIORef)
import Data.Text.IO.Internal (hGetLineWith, readChunk)
import Data.Text.Lazy.Internal (chunk, empty)
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)
#endif
readFile :: FilePath -> IO Text
readFile name = openFile name ReadMode >>= hGetContents
writeFile :: FilePath -> Text -> IO ()
writeFile p = withFile p WriteMode . flip hPutStr
appendFile :: FilePath -> Text -> IO ()
appendFile p = withFile p AppendMode . flip hPutStr
hGetContents :: Handle -> IO Text
#if __GLASGOW_HASKELL__ <= 610
hGetContents = fmap decodeUtf8 . L8.hGetContents
#else
hGetContents h = do
  chooseGoodBuffering h
  wantReadableHandle "hGetContents" h $ \hh -> do
    ts <- lazyRead h
    return (hh{haType=SemiClosedHandle}, ts)
chooseGoodBuffering :: Handle -> IO ()
chooseGoodBuffering h = do
  bufMode <- hGetBuffering h
  when (bufMode == BlockBuffering Nothing) $
    hSetBuffering h (BlockBuffering (Just 16384))
lazyRead :: Handle -> IO Text
lazyRead h = unsafeInterleaveIO $
  withHandle "hGetContents" h $ \hh -> do
    case haType hh of
      ClosedHandle     -> return (hh, L.empty)
      SemiClosedHandle -> lazyReadBuffered h hh
      _                -> ioException 
                          (IOError (Just h) IllegalOperation "hGetContents"
                           "illegal handle type" Nothing Nothing)
lazyReadBuffered :: Handle -> Handle__ -> IO (Handle__, Text)
lazyReadBuffered h hh@Handle__{..} = do
   buf <- readIORef haCharBuffer
   (do t <- readChunk hh buf
       ts <- lazyRead h
       return (hh, chunk t ts)) `catch` \e -> do
         (hh', _) <- hClose_help hh
         if isEOFError e
           then return $ if isEmptyBuffer buf
                         then (hh', empty)
                         else (hh', L.singleton '\r')
           else throw (augmentIOError e "hGetContents" h)
#endif
hGetLine :: Handle -> IO Text
#if __GLASGOW_HASKELL__ <= 610
hGetLine = fmap (decodeUtf8 . L8.fromChunks . (:[])) . S8.hGetLine
#else
hGetLine = hGetLineWith L.fromChunks
#endif
hPutStr :: Handle -> Text -> IO ()
hPutStr h = mapM_ (T.hPutStr h) . L.toChunks
hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn h t = hPutStr h t >> hPutChar h '\n'
interact :: (Text -> Text) -> IO ()
interact f = putStr . f =<< getContents
getContents :: IO Text
getContents = hGetContents stdin
getLine :: IO Text
getLine = hGetLine stdin
putStr :: Text -> IO ()
putStr = hPutStr stdout
putStrLn :: Text -> IO ()
putStrLn = hPutStrLn stdout