{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -cpp #-}
module CIO (
Handle, HandlePosn, IOMode(..), BufferMode(..), SeekMode(..),
stdin, stdout, stderr,
isAlreadyExistsError, isDoesNotExistError, isAlreadyInUseError,
isFullError, isEOFError, isIllegalOperation, isPermissionError,
isUserError,
ioeGetErrorString, ioeGetHandle, ioeGetFileName,
openFileCIO, hCloseCIO,
putCharCIO, putStrCIO, hPutStrCIO, hPutStrLnCIO, writeFileCIO,
readFileCIO, printCIO, getCharCIO, hFlushCIO, hPutCharCIO,
hGetContentsCIO, hSetBufferingCIO, hGetBufferingCIO,
newlineCIO,
doesFileExistCIO, removeFileCIO,
ExitCode(..), exitWithCIO, getArgsCIO, getProgNameCIO,
fileFindInCIO, mktempCIO)
where
import System.IO
import System.IO.Error
import System.Cmd
import System.Directory
import System.Exit
import System.Environment
#if __GLASGOW_HASKELL__ >= 612
import System.IO (hSetEncoding, latin1)
#endif
import FileOps (fileFindIn, mktemp)
import StateBase (PreCST, liftIO)
openFileCIO :: FilePath -> IOMode -> PreCST e s Handle
openFileCIO :: forall e s. FilePath -> IOMode -> PreCST e s Handle
openFileCIO FilePath
p IOMode
m = forall a e s. IO a -> PreCST e s a
liftIO forall a b. (a -> b) -> a -> b
$ do
Handle
hnd <- FilePath -> IOMode -> IO Handle
openFile FilePath
p IOMode
m
#if __GLASGOW_HASKELL__ >= 612
Handle -> TextEncoding -> IO ()
hSetEncoding Handle
hnd TextEncoding
latin1
#endif
forall (m :: * -> *) a. Monad m => a -> m a
return Handle
hnd
hCloseCIO :: Handle -> PreCST e s ()
hCloseCIO :: forall e s. Handle -> PreCST e s ()
hCloseCIO Handle
h = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> IO ()
hClose Handle
h)
putCharCIO :: Char -> PreCST e s ()
putCharCIO :: forall e s. Char -> PreCST e s ()
putCharCIO Char
c = forall a e s. IO a -> PreCST e s a
liftIO (Char -> IO ()
putChar Char
c)
putStrCIO :: String -> PreCST e s ()
putStrCIO :: forall e s. FilePath -> PreCST e s ()
putStrCIO FilePath
s = forall a e s. IO a -> PreCST e s a
liftIO (FilePath -> IO ()
putStr FilePath
s)
hPutStrCIO :: Handle -> String -> PreCST e s ()
hPutStrCIO :: forall e s. Handle -> FilePath -> PreCST e s ()
hPutStrCIO Handle
h FilePath
s = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> FilePath -> IO ()
hPutStr Handle
h FilePath
s)
hPutStrLnCIO :: Handle -> String -> PreCST e s ()
hPutStrLnCIO :: forall e s. Handle -> FilePath -> PreCST e s ()
hPutStrLnCIO Handle
h FilePath
s = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> FilePath -> IO ()
hPutStrLn Handle
h FilePath
s)
writeFileCIO :: FilePath -> String -> PreCST e s ()
writeFileCIO :: forall e s. FilePath -> FilePath -> PreCST e s ()
writeFileCIO FilePath
fname FilePath
contents = do
Handle
hnd <- forall e s. FilePath -> IOMode -> PreCST e s Handle
openFileCIO FilePath
fname IOMode
WriteMode
forall e s. Handle -> FilePath -> PreCST e s ()
hPutStrCIO Handle
hnd FilePath
contents
forall e s. Handle -> PreCST e s ()
hCloseCIO Handle
hnd
readFileCIO :: FilePath -> PreCST e s String
readFileCIO :: forall e s. FilePath -> PreCST e s FilePath
readFileCIO FilePath
fname = do
Handle
hnd <- forall e s. FilePath -> IOMode -> PreCST e s Handle
openFileCIO FilePath
fname IOMode
ReadMode
forall a e s. IO a -> PreCST e s a
liftIO (Handle -> IO FilePath
hGetContents Handle
hnd)
hGetContentsCIO :: Handle -> PreCST e s String
hGetContentsCIO :: forall e s. Handle -> PreCST e s FilePath
hGetContentsCIO Handle
hnd = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> IO FilePath
hGetContents Handle
hnd)
printCIO :: Show a => a -> PreCST e s ()
printCIO :: forall a e s. Show a => a -> PreCST e s ()
printCIO a
a = forall a e s. IO a -> PreCST e s a
liftIO (forall a. Show a => a -> IO ()
print a
a)
getCharCIO :: PreCST e s Char
getCharCIO :: forall e s. PreCST e s Char
getCharCIO = forall a e s. IO a -> PreCST e s a
liftIO IO Char
getChar
hFlushCIO :: Handle -> PreCST e s ()
hFlushCIO :: forall e s. Handle -> PreCST e s ()
hFlushCIO Handle
h = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> IO ()
hFlush Handle
h)
hPutCharCIO :: Handle -> Char -> PreCST e s ()
hPutCharCIO :: forall e s. Handle -> Char -> PreCST e s ()
hPutCharCIO Handle
h Char
ch = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> Char -> IO ()
hPutChar Handle
h Char
ch)
hSetBufferingCIO :: Handle -> BufferMode -> PreCST e s ()
hSetBufferingCIO :: forall e s. Handle -> BufferMode -> PreCST e s ()
hSetBufferingCIO Handle
h BufferMode
m = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> BufferMode -> IO ()
hSetBuffering Handle
h BufferMode
m)
hGetBufferingCIO :: Handle -> PreCST e s BufferMode
hGetBufferingCIO :: forall e s. Handle -> PreCST e s BufferMode
hGetBufferingCIO Handle
h = forall a e s. IO a -> PreCST e s a
liftIO (Handle -> IO BufferMode
hGetBuffering Handle
h)
newlineCIO :: PreCST e s ()
newlineCIO :: forall e s. PreCST e s ()
newlineCIO = forall e s. Char -> PreCST e s ()
putCharCIO Char
'\n'
doesFileExistCIO :: FilePath -> PreCST e s Bool
doesFileExistCIO :: forall e s. FilePath -> PreCST e s Bool
doesFileExistCIO = forall a e s. IO a -> PreCST e s a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
doesFileExist
removeFileCIO :: FilePath -> PreCST e s ()
removeFileCIO :: forall e s. FilePath -> PreCST e s ()
removeFileCIO = forall a e s. IO a -> PreCST e s a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
removeFile
exitWithCIO :: ExitCode -> PreCST e s a
exitWithCIO :: forall e s a. ExitCode -> PreCST e s a
exitWithCIO = forall a e s. IO a -> PreCST e s a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ExitCode -> IO a
exitWith
getArgsCIO :: PreCST e s [String]
getArgsCIO :: forall e s. PreCST e s [FilePath]
getArgsCIO = forall a e s. IO a -> PreCST e s a
liftIO IO [FilePath]
getArgs
getProgNameCIO :: PreCST e s String
getProgNameCIO :: forall e s. PreCST e s FilePath
getProgNameCIO = forall a e s. IO a -> PreCST e s a
liftIO IO FilePath
getProgName
fileFindInCIO :: FilePath -> [FilePath] -> PreCST e s FilePath
fileFindInCIO :: forall e s. FilePath -> [FilePath] -> PreCST e s FilePath
fileFindInCIO FilePath
file [FilePath]
paths = forall a e s. IO a -> PreCST e s a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath
file FilePath -> [FilePath] -> IO FilePath
`fileFindIn` [FilePath]
paths
mktempCIO :: FilePath -> FilePath -> PreCST e s (Handle, FilePath)
mktempCIO :: forall e s. FilePath -> FilePath -> PreCST e s (Handle, FilePath)
mktempCIO FilePath
pre FilePath
post = forall a e s. IO a -> PreCST e s a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO (Handle, FilePath)
mktemp FilePath
pre FilePath
post