module Foundation.IO.File
( FilePath
, openFile
, closeFile
, IOMode(..)
, withFile
, hGet
, hGetNonBlocking
, hGetSome
, hPut
, readFile
) where
import System.IO (Handle, IOMode)
import System.IO.Error
import qualified System.IO as S
import Foundation.Collection
import Foundation.VFS
import Basement.Types.OffsetSize
import Basement.Imports
import Foundation.Array.Internal
import Foundation.Numerical
import qualified Basement.UArray.Mutable as V
import qualified Basement.UArray as V
import Control.Exception (bracket)
import Foreign.Ptr (plusPtr)
openFile :: FilePath -> IOMode -> IO Handle
openFile filepath mode = do
S.openBinaryFile (filePathToLString filepath) mode
closeFile :: Handle -> IO ()
closeFile = S.hClose
hGet :: Handle -> Int -> IO (UArray Word8)
hGet h size
| size < 0 = invalidBufferSize "hGet" h size
| otherwise = V.createFromIO (CountOf size) $ \p -> (CountOf <$> S.hGetBuf h p size)
hGetNonBlocking :: Handle -> Int -> IO (UArray Word8)
hGetNonBlocking h size
| size < 0 = invalidBufferSize "hGetNonBlocking" h size
| otherwise = V.createFromIO (CountOf size) $ \p -> (CountOf <$> S.hGetBufNonBlocking h p size)
hGetSome :: Handle -> Int -> IO (UArray Word8)
hGetSome h size
| size < 0 = invalidBufferSize "hGetSome" h size
| otherwise = V.createFromIO (CountOf size) $ \p -> (CountOf <$> S.hGetBufSome h p size)
hPut :: Handle -> (UArray Word8) -> IO ()
hPut h arr = withPtr arr $ \ptr -> S.hPutBuf h ptr (let (CountOf sz) = length arr in sz)
invalidBufferSize :: [Char] -> Handle -> Int -> IO a
invalidBufferSize functionName handle size =
ioError $ mkIOError illegalOperationErrorType
(functionName <> " invalid array size: " <> toList (show size))
(Just handle)
Nothing
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile fp mode act = bracket (openFile fp mode) closeFile act
readFile :: FilePath -> IO (UArray Word8)
readFile fp = withFile fp S.ReadMode $ \h -> do
sz <- S.hFileSize h
mv <- V.newPinned (CountOf $ fromInteger sz)
V.withMutablePtr mv $ loop h (fromInteger sz)
unsafeFreeze mv
where
loop h left dst
| left == 0 = return ()
| otherwise = do
let toRead = min blockSize left
r <- S.hGetBuf h dst toRead
if r > 0 && r <= toRead
then loop h (left r) (dst `plusPtr` r)
else error "readFile: "
blockSize :: Int
blockSize = 4096