{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
module GHC.IO.StdHandles
(
stdin, stdout, stderr,
openFile, openBinaryFile, openFileBlocking,
withFile, withBinaryFile, withFileBlocking
) where
import GHC.IO
import GHC.IO.IOMode
import GHC.IO.Handle.Types
import qualified GHC.IO.Handle.FD as POSIX
#if defined(mingw32_HOST_OS)
import GHC.IO.SubSystem
import qualified GHC.IO.Handle.Windows as Win
import GHC.IO.Handle.Internals (hClose_impl)
stdin :: Handle
stdin = POSIX.stdin <!> Win.stdin
stdout :: Handle
stdout = POSIX.stdout <!> Win.stdout
stderr :: Handle
stderr = POSIX.stderr <!> Win.stderr
openFile :: FilePath -> IOMode -> IO Handle
openFile = POSIX.openFile <!> Win.openFile
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile = POSIX.withFile <!> wf
where
wf path mode act = bracket (Win.openFile path mode) hClose_impl act
openBinaryFile :: FilePath -> IOMode -> IO Handle
openBinaryFile = POSIX.openBinaryFile <!> Win.openBinaryFile
withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile = POSIX.withBinaryFile <!> wf
where
wf path mode act = bracket (Win.openBinaryFile path mode) hClose_impl act
openFileBlocking :: FilePath -> IOMode -> IO Handle
openFileBlocking = POSIX.openFileBlocking <!> Win.openFileBlocking
withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFileBlocking = POSIX.withFileBlocking <!> wf
where
wf path mode act = bracket (Win.openFileBlocking path mode) hClose_impl act
#else
stdin :: Handle
stdin :: Handle
stdin = Handle
POSIX.stdin
stdout :: Handle
stdout :: Handle
stdout = Handle
POSIX.stdout
stderr :: Handle
stderr :: Handle
stderr = Handle
POSIX.stderr
openFile :: FilePath -> IOMode -> IO Handle
openFile :: FilePath -> IOMode -> IO Handle
openFile = FilePath -> IOMode -> IO Handle
POSIX.openFile
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile :: forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile = FilePath -> IOMode -> (Handle -> IO r) -> IO r
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
POSIX.withFile
openBinaryFile :: FilePath -> IOMode -> IO Handle
openBinaryFile :: FilePath -> IOMode -> IO Handle
openBinaryFile = FilePath -> IOMode -> IO Handle
POSIX.openBinaryFile
withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile :: forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile = FilePath -> IOMode -> (Handle -> IO r) -> IO r
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
POSIX.withBinaryFile
openFileBlocking :: FilePath -> IOMode -> IO Handle
openFileBlocking :: FilePath -> IOMode -> IO Handle
openFileBlocking = FilePath -> IOMode -> IO Handle
POSIX.openFileBlocking
withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFileBlocking :: forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFileBlocking = FilePath -> IOMode -> (Handle -> IO r) -> IO r
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
POSIX.withFileBlocking
#endif