module System.IO.ExplicitIOModes
(
SIO.IO
, SIO.fixIO
, SIO.FilePath
, Handle
, ReadMode
, WriteMode
, AppendMode
, ReadWriteMode
, ReadModes
, WriteModes
, IOMode(..)
, MkIOMode(mkIOMode)
, regularIOMode
, stdin
, stdout
, stderr
, cast
, CheckMode
, openFile
, withFile
, openFile'
, withFile'
, hClose
, SIO.readFile
, SIO.writeFile
, SIO.appendFile
, hFileSize
#ifdef __GLASGOW_HASKELL__
, hSetFileSize
#endif
, hIsEOF
, SIO.isEOF
, SIO.BufferMode(..)
, hSetBuffering
, hGetBuffering
, hFlush
, hGetPosn
, SIO.hSetPosn
, SIO.HandlePosn
, hSeek
, SIO.SeekMode(..)
#if !defined(__NHC__)
, hTell
#endif
, hIsOpen, hIsClosed
, hIsReadable, hIsWritable
, hIsSeekable
#if !defined(__NHC__)
, hIsTerminalDevice
, hSetEcho
, hGetEcho
#endif
#ifdef __GLASGOW_HASKELL__
, hShow
#endif
, hWaitForInput
, hReady
, hGetChar
, hGetLine
, hLookAhead
, hGetContents
, hPutChar
, hPutStr
, hPutStrLn
, hPrint
, SIO.interact
, SIO.putChar
, SIO.putStr
, SIO.putStrLn
, SIO.print
, SIO.getChar
, SIO.getLine
, SIO.getContents
, SIO.readIO
, SIO.readLn
, openBinaryFile
, withBinaryFile
, openBinaryFile'
, withBinaryFile'
, hSetBinaryMode
, hPutBuf
, hGetBuf
#if !defined(__NHC__) && !defined(__HUGS__)
, hPutBufNonBlocking
, hGetBufNonBlocking
#endif
, openTempFile
, openBinaryTempFile
#if MIN_VERSION_base(4,2,0)
, openTempFileWithDefaultPermissions
, openBinaryTempFileWithDefaultPermissions
#endif
#if MIN_VERSION_base(4,2,0) && !defined(__NHC__) && !defined(__HUGS__)
, hSetEncoding
, hGetEncoding
, SIO.TextEncoding
, SIO.latin1
, SIO.utf8, SIO.utf8_bom
, SIO.utf16, SIO.utf16le, SIO.utf16be
, SIO.utf32, SIO.utf32le, SIO.utf32be
, SIO.localeEncoding
, SIO.mkTextEncoding
, hSetNewlineMode
, SIO.Newline(..)
, SIO.nativeNewline
, SIO.NewlineMode(..)
, SIO.noNewlineTranslation, SIO.universalNewlineMode, SIO.nativeNewlineMode
#endif
) where
import Prelude ( Integer )
import Control.Monad ( return, (>>=), fail, liftM, liftM2 )
import Control.Arrow ( second )
import Foreign.Ptr ( Ptr )
import Data.Eq ( Eq, (==) )
import Data.Ord ( Ord, (<=) )
import Data.Function ( ($) )
import Data.Bool ( Bool(False, True) )
import Data.Maybe ( Maybe(Nothing, Just) )
import Data.Int ( Int )
import Data.Char ( Char, String )
import Text.Show ( Show, show )
import System.IO ( IO, FilePath )
import qualified System.IO as SIO
import Data.Function.Unicode ( (∘) )
import Data.Bool.Unicode ( (∧) )
import Data.Tagged ( Tagged(Tagged), unTagged )
import System.IO.ExplicitIOModes.Internal ( Handle(Handle) )
import System.IO.ExplicitIOModes.Unsafe ( wrap )
data ReadMode
data WriteMode
data AppendMode
data ReadWriteMode
class ReadModes ioMode
class WriteModes ioMode
instance ReadModes ReadMode
instance ReadModes ReadWriteMode
instance WriteModes WriteMode
instance WriteModes AppendMode
instance WriteModes ReadWriteMode
data IOMode ioMode where
ReadMode ∷ IOMode ReadMode
WriteMode ∷ IOMode WriteMode
AppendMode ∷ IOMode AppendMode
ReadWriteMode ∷ IOMode ReadWriteMode
class MkIOMode ioMode where
mkIOMode ∷ IOMode ioMode
instance MkIOMode ReadMode where mkIOMode = ReadMode
instance MkIOMode WriteMode where mkIOMode = WriteMode
instance MkIOMode AppendMode where mkIOMode = AppendMode
instance MkIOMode ReadWriteMode where mkIOMode = ReadWriteMode
regularIOMode ∷ IOMode ioMode → SIO.IOMode
regularIOMode ReadMode = SIO.ReadMode
regularIOMode WriteMode = SIO.WriteMode
regularIOMode AppendMode = SIO.AppendMode
regularIOMode ReadWriteMode = SIO.ReadWriteMode
instance Eq (IOMode ioMode) where
ReadMode == ReadMode = True
WriteMode == WriteMode = True
AppendMode == AppendMode = True
ReadWriteMode == ReadWriteMode = True
_ == _ = False
instance Ord (IOMode ioMode) where
ReadWriteMode <= ReadWriteMode = True
ReadWriteMode <= _ = False
AppendMode <= ReadWriteMode = True
AppendMode <= AppendMode = True
AppendMode <= _ = False
WriteMode <= ReadWriteMode = True
WriteMode <= AppendMode = True
WriteMode <= WriteMode = True
WriteMode <= _ = False
ReadMode <= ReadWriteMode = True
ReadMode <= AppendMode = True
ReadMode <= WriteMode = True
ReadMode <= ReadMode = True
instance Show (IOMode ioMode) where
show ReadMode = "ReadMode"
show WriteMode = "WriteMode"
show AppendMode = "AppendMode"
show ReadWriteMode = "ReadWriteMode"
stdin ∷ Handle ReadMode
stdin = Handle SIO.stdin
stdout ∷ Handle WriteMode
stdout = Handle SIO.stdout
stderr ∷ Handle WriteMode
stderr = Handle SIO.stderr
cast ∷ ∀ anyIOMode castedIOMode. CheckMode castedIOMode
⇒ Handle anyIOMode → IO (Maybe (Handle castedIOMode))
cast (Handle h) = do
b ← unTagged (checkMode ∷ Tagged castedIOMode (SIO.Handle → IO Bool)) h
return $ if b
then Just $ Handle h
else Nothing
class CheckMode ioMode where
checkMode ∷ Tagged ioMode (SIO.Handle → IO Bool)
instance CheckMode ReadMode where checkMode = Tagged SIO.hIsReadable
instance CheckMode WriteMode where checkMode = Tagged SIO.hIsWritable
instance CheckMode AppendMode where checkMode = Tagged SIO.hIsWritable
instance CheckMode ReadWriteMode where checkMode = Tagged $
\h → liftM2 (∧) (SIO.hIsReadable h)
(SIO.hIsWritable h)
openFile ∷ FilePath → IOMode ioMode → IO (Handle ioMode)
openFile fp = liftM Handle ∘ SIO.openFile fp ∘ regularIOMode
withFile ∷ FilePath → IOMode ioMode → (Handle ioMode → IO α) → IO α
withFile fp ioMode f = SIO.withFile fp (regularIOMode ioMode) $ f ∘ Handle
openFile' ∷ MkIOMode ioMode ⇒ FilePath → IO (Handle ioMode)
openFile' fp = openFile fp mkIOMode
withFile' ∷ MkIOMode ioMode ⇒ FilePath → (Handle ioMode → IO α) → IO α
withFile' fp = withFile fp mkIOMode
hClose ∷ Handle ioMode → IO ()
hClose = wrap SIO.hClose
hFileSize ∷ Handle ioMode → IO Integer
hFileSize = wrap SIO.hFileSize
#ifdef __GLASGOW_HASKELL__
hSetFileSize ∷ Handle ioMode → Integer → IO ()
hSetFileSize = wrap SIO.hSetFileSize
#endif
hIsEOF ∷ ReadModes ioMode ⇒ Handle ioMode → IO Bool
hIsEOF = wrap SIO.hIsEOF
hSetBuffering ∷ Handle ioMode → SIO.BufferMode → IO ()
hSetBuffering = wrap SIO.hSetBuffering
hGetBuffering ∷ Handle ioMode → IO SIO.BufferMode
hGetBuffering = wrap SIO.hGetBuffering
hFlush ∷ Handle ioMode → IO ()
hFlush = wrap SIO.hFlush
hGetPosn ∷ Handle ioMode → IO SIO.HandlePosn
hGetPosn = wrap SIO.hGetPosn
hSeek ∷ Handle ioMode → SIO.SeekMode → Integer → IO ()
hSeek = wrap SIO.hSeek
#if !defined(__NHC__)
hTell ∷ Handle ioMode → IO Integer
hTell = wrap SIO.hTell
#endif
hIsOpen ∷ Handle ioMode → IO Bool
hIsOpen = wrap SIO.hIsOpen
hIsClosed ∷ Handle ioMode → IO Bool
hIsClosed = wrap SIO.hIsClosed
hIsReadable ∷ Handle ioMode → IO Bool
hIsReadable = wrap SIO.hIsReadable
hIsWritable ∷ Handle ioMode → IO Bool
hIsWritable = wrap SIO.hIsWritable
hIsSeekable ∷ Handle ioMode → IO Bool
hIsSeekable = wrap SIO.hIsSeekable
#if !defined(__NHC__)
hIsTerminalDevice ∷ Handle ioMode → IO Bool
hIsTerminalDevice = wrap SIO.hIsTerminalDevice
hSetEcho ∷ Handle ioMode → Bool → IO ()
hSetEcho = wrap SIO.hSetEcho
hGetEcho ∷ Handle ioMode → IO Bool
hGetEcho = wrap SIO.hGetEcho
#endif
#ifdef __GLASGOW_HASKELL__
hShow ∷ Handle ioMode → IO String
hShow = wrap SIO.hShow
#endif
hWaitForInput ∷ ReadModes ioMode ⇒ Handle ioMode → Int → IO Bool
hWaitForInput = wrap SIO.hWaitForInput
hReady ∷ ReadModes ioMode ⇒ Handle ioMode → IO Bool
hReady = wrap SIO.hReady
hGetChar ∷ ReadModes ioMode ⇒ Handle ioMode → IO Char
hGetChar = wrap SIO.hGetChar
hGetLine ∷ ReadModes ioMode ⇒ Handle ioMode → IO String
hGetLine = wrap SIO.hGetLine
hLookAhead ∷ ReadModes ioMode ⇒ Handle ioMode → IO Char
hLookAhead = wrap SIO.hLookAhead
hGetContents ∷ ReadModes ioMode ⇒ Handle ioMode → IO String
hGetContents = wrap SIO.hGetContents
hPutChar ∷ WriteModes ioMode ⇒ Handle ioMode → Char → IO ()
hPutChar = wrap SIO.hPutChar
hPutStr ∷ WriteModes ioMode ⇒ Handle ioMode → String → IO ()
hPutStr = wrap SIO.hPutStr
hPutStrLn ∷ WriteModes ioMode ⇒ Handle ioMode → String → IO ()
hPutStrLn = wrap SIO.hPutStrLn
hPrint ∷ (WriteModes ioMode, Show α) ⇒ Handle ioMode → α → IO ()
hPrint = wrap SIO.hPrint
openBinaryFile ∷ FilePath → IOMode ioMode → IO (Handle ioMode)
openBinaryFile fp = liftM Handle ∘ SIO.openBinaryFile fp ∘ regularIOMode
withBinaryFile ∷ FilePath → IOMode ioMode → (Handle ioMode → IO α) → IO α
withBinaryFile fp ioMode f = SIO.withBinaryFile fp (regularIOMode ioMode) $ f ∘ Handle
openBinaryFile' ∷ MkIOMode ioMode ⇒ FilePath → IO (Handle ioMode)
openBinaryFile' fp = openBinaryFile fp mkIOMode
withBinaryFile' ∷ MkIOMode ioMode ⇒ FilePath → (Handle ioMode → IO α) → IO α
withBinaryFile' fp = withBinaryFile fp mkIOMode
hSetBinaryMode ∷ Handle ioMode → Bool → IO ()
hSetBinaryMode = wrap SIO.hSetBinaryMode
hPutBuf ∷ WriteModes ioMode ⇒ Handle ioMode → Ptr α → Int → IO ()
hPutBuf = wrap SIO.hPutBuf
hGetBuf ∷ ReadModes ioMode ⇒ Handle ioMode → Ptr α → Int → IO Int
hGetBuf = wrap SIO.hGetBuf
#if !defined(__NHC__) && !defined(__HUGS__)
hPutBufNonBlocking ∷ WriteModes ioMode ⇒ Handle ioMode → Ptr α → Int → IO Int
hPutBufNonBlocking = wrap SIO.hPutBufNonBlocking
hGetBufNonBlocking ∷ ReadModes ioMode ⇒ Handle ioMode → Ptr α → Int → IO Int
hGetBufNonBlocking = wrap SIO.hGetBufNonBlocking
#endif
openTempFile ∷ FilePath → String → IO (FilePath, Handle ReadWriteMode)
openTempFile fp template =
liftM (second Handle) $ SIO.openTempFile fp template
openBinaryTempFile ∷ FilePath → String → IO (FilePath, Handle ReadWriteMode)
openBinaryTempFile fp template =
liftM (second Handle) $ SIO.openBinaryTempFile fp template
#if MIN_VERSION_base(4,2,0)
openTempFileWithDefaultPermissions ∷ FilePath → String → IO (FilePath, Handle ReadWriteMode)
openTempFileWithDefaultPermissions fp template =
liftM (second Handle) $ SIO.openTempFileWithDefaultPermissions fp template
openBinaryTempFileWithDefaultPermissions ∷ FilePath → String → IO (FilePath, Handle ReadWriteMode)
openBinaryTempFileWithDefaultPermissions fp template =
liftM (second Handle) $ SIO.openBinaryTempFileWithDefaultPermissions fp template
#endif
#if MIN_VERSION_base(4,2,0) && !defined(__NHC__) && !defined(__HUGS__)
hSetEncoding ∷ Handle ioMode → SIO.TextEncoding → IO ()
hSetEncoding = wrap SIO.hSetEncoding
hGetEncoding ∷ Handle ioMode → IO (Maybe SIO.TextEncoding)
hGetEncoding = wrap SIO.hGetEncoding
hSetNewlineMode ∷ Handle ioMode → SIO.NewlineMode → IO ()
hSetNewlineMode = wrap SIO.hSetNewlineMode
#endif