{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RecordWildCards #-}
module System.IO.ExceptionFree.Internal.Custom ( readFile, FileContents ) where
import Data.Foldable (foldr)
import Control.Applicative ((<$>))
import Control.Monad ((>>=), (>>), when, return)
import Data.Bool
import Data.Char
import Data.Either (Either(..))
import Data.Eq ((==))
import Data.Function (($), (.))
import Data.Int
import Data.List (null, concat, reverse)
import Data.Maybe (Maybe(..))
import Data.Monoid ((<>))
import Data.Ord ((<), (>))
import Data.String (String)
import Foreign.Storable (peekElemOff)
import GHC.IO (unsafeInterleaveIO)
import GHC.IO.Buffer (Buffer(..), isWriteBuffer, isEmptyBuffer, BufferState(..), CharBuffer(..), RawCharBuffer, withRawBuffer, bufferAdjustL, readCharBuf, writeCharBuf, bufferElems, newCharBuffer)
import GHC.IO.Exception (IOException(..), IOError(..), IOErrorType(..))
import GHC.IO.Handle.Internals (decodeByteBuf, debugIO)
import GHC.IO.Handle.Types (Handle(..), Handle__(..), HandleType(..), checkHandleInvariants)
import GHC.IORef (readIORef, writeIORef)
import GHC.MVar (MVar, putMVar, takeMVar)
import GHC.Num ((-), (+))
import GHC.Show (show)
import System.IO (FilePath, IO, openFile, IOMode(..), Handle(..), Newline(..), putStrLn)
import qualified GHC.IO.BufferedIO as Buffered
type FileContents = String
data ReadProgress = InProgress
| Complete
delayedReadError :: Handle -> IOError
delayedReadError handle = IOError (Just handle) IllegalOperation "hGetContents" "delayed read on closed handle" Nothing Nothing
illegalHandleTypeError :: Handle -> HandleType -> IOError
illegalHandleTypeError handle handleType = IOError (Just handle) IllegalOperation "hGetContents" msg Nothing Nothing
where
msg = "illegal handle type [" <> show handleType <> "]"
unexpectedFailureError :: IOError
unexpectedFailureError = IOError Nothing IllegalOperation "hGetContents" "unexpected failure" Nothing Nothing
emptyFileError :: IOError
emptyFileError = IOError Nothing IllegalOperation "hGetContents" "empty file" Nothing Nothing
readFile :: FilePath -> IO (Either IOError FileContents)
readFile path = openFile path ReadMode >>= hGetContents
hGetContents :: Handle -> IO (Either IOError FileContents)
hGetContents h@(FileHandle _ mvar) = unsafeInterleaveIO (attemptUnsafeRead h mvar)
hGetContents h@(DuplexHandle _ mvar _) = unsafeInterleaveIO (attemptUnsafeRead h mvar)
{-# INLINE attemptUnsafeRead #-}
attemptUnsafeRead :: Handle -> MVar Handle__ -> IO (Either IOError FileContents)
attemptUnsafeRead handle mvar = takeMVar mvar
>>= \innerHandle -> case haType innerHandle of
ReadHandle -> unsafeRead InProgress [] innerHandle
>>= \res -> putMVar mvar innerHandle
>> return res
SemiClosedHandle -> putMVar mvar innerHandle >> return (Left unexpectedFailureError)
ClosedHandle -> putMVar mvar innerHandle >> return (Left (delayedReadError handle))
handleType -> putMVar mvar innerHandle >> return (Left (illegalHandleTypeError handle handleType))
unsafeRead :: ReadProgress -> [String] -> Handle__ -> IO (Either IOError FileContents)
unsafeRead Complete !acc innerHandle@Handle__{..} = return $ Right $ foldr (<>) "" acc
unsafeRead InProgress !acc innerHandle@Handle__{..} =
readIORef haByteBuffer
>>= \buf -> Buffered.fillReadBuffer0 haDevice buf
>>= \(maybeBytesRead, buf') -> case maybeBytesRead of
Nothing -> unsafeRead Complete acc innerHandle
Just bytesRead -> writeIORef haByteBuffer buf'
>> newCharBuffer bytesRead ReadBuffer
>>= \cbuf -> decodeByteBuf innerHandle cbuf
>>= \decoded -> unpack (bufRaw decoded) (bufL decoded) (bufR decoded) []
>>= \s -> unsafeRead InProgress (s:acc) innerHandle
#define CHARBUF_UTF32
{-# INLINE unpack #-}
unpack :: RawCharBuffer -> Int -> Int -> String -> IO String
unpack !buf !r !w acc0
| r == w = return acc0
| otherwise =
withRawBuffer buf $ \pbuf ->
let
unpackRB acc !i
| i < r = return acc
| otherwise = do
#if defined(CHARBUF_UTF16)
c2 <- peekElemOff pbuf i
if (c2 < 0xdc00 || c2 > 0xdffff)
then unpackRB (unsafeChr (fromIntegral c2) : acc) (i-1)
else do c1 <- peekElemOff pbuf (i-1)
let c = (fromIntegral c1 - 0xd800) * 0x400 +
(fromIntegral c2 - 0xdc00) + 0x10000
case desurrogatifyRoundtripCharacter (unsafeChr c) of
{ C# c# -> unpackRB (C# c# : acc) (i-2) }
#else
c <- peekElemOff pbuf i
unpackRB (c : acc) (i-1)
#endif
in
unpackRB acc0 (w-1)