- data IO a
- run :: Maybe FilePath -> [Handle] -> IO a -> IO a
- class Monad m => JailIO m where
- type FilePath = String
- data Handle
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
- withFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a
- openFile :: FilePath -> IOMode -> IO Handle
- data IOMode
- = ReadMode
- | WriteMode
- | AppendMode
- | ReadWriteMode
- hClose :: Handle -> IO ()
- readFile :: FilePath -> IO String
- writeFile :: FilePath -> String -> IO ()
- appendFile :: FilePath -> String -> IO ()
- hFileSize :: Handle -> IO Integer
- hSetFileSize :: Handle -> Integer -> IO ()
- hIsEOF :: Handle -> IO Bool
- isEOF :: IO Bool
- data BufferMode
- = NoBuffering
- | LineBuffering
- | BlockBuffering (Maybe Int)
- hSetBuffering :: Handle -> BufferMode -> IO ()
- hGetBuffering :: Handle -> IO BufferMode
- hFlush :: Handle -> IO ()
- hGetPosn :: Handle -> IO HandlePosn
- hSetPosn :: HandlePosn -> IO ()
- data HandlePosn
- hSeek :: Handle -> SeekMode -> Integer -> IO ()
- data SeekMode
- hTell :: Handle -> IO Integer
- hIsOpen :: Handle -> IO Bool
- hIsClosed :: Handle -> IO Bool
- hIsReadable :: Handle -> IO Bool
- hIsWritable :: Handle -> IO Bool
- hIsSeekable :: Handle -> IO Bool
- hIsTerminalDevice :: Handle -> IO Bool
- hSetEcho :: Handle -> Bool -> IO ()
- hGetEcho :: Handle -> IO Bool
- hShow :: Handle -> IO String
- hWaitForInput :: Handle -> Int -> IO Bool
- hReady :: Handle -> IO Bool
- hGetChar :: Handle -> IO Char
- hGetLine :: Handle -> IO String
- hLookAhead :: Handle -> IO Char
- hGetContents :: Handle -> IO String
- hPutChar :: Handle -> Char -> IO ()
- hPutStr :: Handle -> String -> IO ()
- hPutStrLn :: Handle -> String -> IO ()
- hPrint :: Show a => Handle -> a -> IO ()
- interact :: (String -> String) -> IO ()
- putChar :: Char -> IO ()
- putStr :: String -> IO ()
- putStrLn :: String -> IO ()
- print :: Show a => a -> IO ()
- getChar :: IO Char
- getLine :: IO String
- getContents :: IO String
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- withBinaryFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a
- openBinaryFile :: FilePath -> IOMode -> IO Handle
- hSetBinaryMode :: Handle -> Bool -> IO ()
- hPutBuf :: Handle -> Ptr a -> Int -> IO ()
- hGetBuf :: Handle -> Ptr a -> Int -> IO Int
- hPutBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int
- hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int
- openTempFile :: FilePath -> String -> IO (FilePath, Handle)
- openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
The IO monad
The jailed IO monad.
:: Maybe FilePath | The jail directory or |
-> [Handle] | A white list of handles that are always accessible. |
-> IO a | The jailed IO computation to run. |
-> IO a | Run the computation from within the insecure real world. |
Run a jailed IO computation. The IO computation will be able to access all
files that are within the specified jail directory. All file accesses outside
the jail directory will be refused. Only file handles opened from within the
jailed computation and the handles from the white list will be accessible to
the operations requiring a file handle. No smuggling in of foreign handles,
border patrol is very strict. When the jail path is specified as Nothing
no
file access will be possible at all, this means the computation can only rely
on the white listed handles.
class Monad m => JailIO m whereSource
Like MonadIO
, but for jailed computations.
JailIO IO | |
JailIO m => JailIO (ListT m) | |
JailIO m => JailIO (IdentityT m) | |
(Error e, JailIO m) => JailIO (ErrorT e m) | |
JailIO m => JailIO (ContT r m) | |
JailIO m => JailIO (ReaderT r m) | |
JailIO m => JailIO (StateT r m) | |
(Monoid r, JailIO m) => JailIO (WriterT r m) | |
(Monoid w, JailIO m) => JailIO (RWST r w s m) |
Files and handles
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
data Handle
Haskell defines operations to read and write characters from and to files,
represented by values of type Handle
. Each value of this type is a
handle: a record used by the Haskell run-time system to manage I/O
with file system objects. A handle has at least the following properties:
- whether it manages input or output or both;
- whether it is open, closed or semi-closed;
- whether the object is seekable;
- whether buffering is disabled, or enabled on a line or block basis;
- a buffer (whose length may be zero).
Most handles will also have a current I/O position indicating where the next
input or output operation will occur. A handle is readable if it
manages only input or both input and output; likewise, it is writable if
it manages only output or both input and output. A handle is open when
first allocated.
Once it is closed it can no longer be used for either input or output,
though an implementation cannot re-use its storage while references
remain to it. Handles are in the Show
and Eq
classes. The string
produced by showing a handle is system dependent; it should include
enough information to identify the handle for debugging. A handle is
equal according to ==
only to itself; no attempt
is made to compare the internal state of different handles for equality.
GHC note: a Handle
will be automatically closed when the garbage
collector detects that it has become unreferenced by the program.
However, relying on this behaviour is not generally recommended:
the garbage collector is unpredictable. If possible, use explicit
an explicit hClose to close Handle
s when they are no longer
required. GHC does not currently attempt to free up file
descriptors when they have run out, it is your responsibility to
ensure that this doesn't happen.
Three handles are allocated during program initialisation, and are initially open.
Opening and closing files
Opening files
data IOMode
Closing files
Special cases
File locking
Operations on handles
Determining and changing the size of a file
Detecting the end of input
Buffering operations
data BufferMode
Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:
- line-buffering: the entire output buffer is flushed whenever a newline is output, the buffer overflows, a System.IO.hFlush is issued, or the handle is closed.
- block-buffering: the entire buffer is written out whenever it overflows, a System.IO.hFlush is issued, or the handle is closed.
- no-buffering: output is written immediately, and never stored in the buffer.
An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.
Similarly, input occurs according to the buffer mode for the handle:
- line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
- block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
- no-buffering: the next input item is read and returned. The System.IO.hLookAhead operation implies that even a no-buffered handle may require a one-character buffer.
The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.
NoBuffering | buffering is disabled if possible. |
LineBuffering | line-buffering should be enabled if possible. |
BlockBuffering (Maybe Int) | block-buffering should be enabled if possible.
The size of the buffer is |
hSetBuffering :: Handle -> BufferMode -> IO ()Source
Repositioning handles
hGetPosn :: Handle -> IO HandlePosnSource
hSetPosn :: HandlePosn -> IO ()Source
data HandlePosn
data SeekMode
A mode that determines the effect of hSeek hdl mode i
, as follows:
AbsoluteSeek | the position of |
RelativeSeek | the position of |
SeekFromEnd | the position of |
Handle properties
hIsReadable :: Handle -> IO BoolSource
hIsWritable :: Handle -> IO BoolSource
hIsSeekable :: Handle -> IO BoolSource
Terminal operations (not portable: GHC/Hugs only)
hIsTerminalDevice :: Handle -> IO BoolSource
Showing handle state (not portable: GHC only)
Text input and output
Text input
hLookAhead :: Handle -> IO CharSource
hGetContents :: Handle -> IO StringSource