{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} module System.FilePath.FilePather.IO( readFile , readFile' , appendFile , writeFile , withFile , openFile , withBinaryFile , openBinaryFile , openTempFile , openBinaryTempFile , openTempFileWithDefaultPermissions , openBinaryTempFileWithDefaultPermissions ) where import Control.Exception ( Exception ) import Data.String ( String ) import System.FilePath(FilePath) import System.FilePath.FilePather.ReadFilePath ( ReadFilePathT, tryReadFilePath ) import qualified System.IO as I ( appendFile, readFile, writeFile, openBinaryFile, openFile, openBinaryTempFile, openBinaryTempFileWithDefaultPermissions, openTempFile, openTempFileWithDefaultPermissions, readFile', withBinaryFile, withFile ) import System.IO(IO, IOMode, Handle) readFile :: Exception e => ReadFilePathT e IO String readFile = tryReadFilePath I.readFile {-# INLINE readFile #-} readFile' :: Exception e => ReadFilePathT e IO String readFile' = tryReadFilePath I.readFile' {-# INLINE readFile' #-} appendFile :: Exception e => String -> ReadFilePathT e IO () appendFile s = tryReadFilePath (`I.appendFile` s) {-# INLINE appendFile #-} writeFile :: Exception e => String -> ReadFilePathT e IO () writeFile s = tryReadFilePath (`I.writeFile` s) {-# INLINE writeFile #-} withFile :: Exception e => IOMode -> (Handle -> IO r) -> ReadFilePathT e IO r withFile mode k = tryReadFilePath (\p -> I.withFile p mode k) {-# INLINE withFile #-} openFile :: Exception e => IOMode -> ReadFilePathT e IO Handle openFile mode = tryReadFilePath (`I.openFile` mode) {-# INLINE openFile #-} withBinaryFile :: Exception e => IOMode -> (Handle -> IO r) -> ReadFilePathT e IO r withBinaryFile mode k = tryReadFilePath (\p -> I.withBinaryFile p mode k) {-# INLINE withBinaryFile #-} openBinaryFile :: Exception e => IOMode -> ReadFilePathT e IO Handle openBinaryFile mode = tryReadFilePath (`I.openBinaryFile` mode) {-# INLINE openBinaryFile #-} openTempFile :: Exception e => String -> ReadFilePathT e IO (FilePath, Handle) openTempFile s = tryReadFilePath (`I.openTempFile` s) {-# INLINE openTempFile #-} openBinaryTempFile :: Exception e => String -> ReadFilePathT e IO (FilePath, Handle) openBinaryTempFile s = tryReadFilePath (`I.openBinaryTempFile` s) {-# INLINE openBinaryTempFile #-} openTempFileWithDefaultPermissions :: Exception e => String -> ReadFilePathT e IO (FilePath, Handle) openTempFileWithDefaultPermissions s = tryReadFilePath (`I.openTempFileWithDefaultPermissions` s) {-# INLINE openTempFileWithDefaultPermissions #-} openBinaryTempFileWithDefaultPermissions :: Exception e => String -> ReadFilePathT e IO (FilePath, Handle) openBinaryTempFileWithDefaultPermissions s = tryReadFilePath (`I.openBinaryTempFileWithDefaultPermissions` s) {-# INLINE openBinaryTempFileWithDefaultPermissions #-}