Raw I/O library proposal, second (more pragmatic) draft

Ben Rudiak-Gould libraries@haskell.org
Thu, 31 Jul 2003 15:06:04 -0700 (PDT)


[Crossposted to Haskell and Libraries. Replies to Libraries.]


-- More comments, please. Bad names? Important missing functionality?
-- Still unimplementable?


module System.RawIOSecondDraft (...) where

data File		-- now essentially a file handle
data InputChannel	-- renamed for less confusing function prefixes
data OutputChannel

-- | A Moniker is a slight generalization of a pathname. In principle this
-- could be extended to support URIs, host:port SSL connections, memory
-- buffers, and so on, though it might be better to give them their own
-- functions.

-- "Compatibility" refers to compatibility with existing Haskell
-- implementations, which treat Char values like octets. RawPathname is
-- there to avoid an octet -> string -> octet translation in cases where
-- that's undesirable. This is slightly problematic on Win32, where
-- pathnames really *are* strings.

type Moniker
  = Pathname String
  | CompatibilityPathname String
  | RawPathname [Octet]

{- if supported, maybe:
  | DirectoryEntry Directory String
  | ResourceFork Moniker
  | NamedFork String Moniker
-}


-- * File and channel creation functions

-- I still use "lookup" rather than "open" to emphasize that there's an
-- irreversible and time-dependent translation going on here.

lookupFileRO              :: Moniker -> IO File
lookupFileRW              :: Moniker -> IO File
lookupInputChannel        :: Moniker -> IO InputChannel
lookupOutputChannelAppend :: Moniker -> IO OutputChannel
createOutputChannel       :: Moniker -> IO OutputChannel

-- * File access functions

-- | Indicates that a File value will never be used again. Calling
-- fRelease is not mandatory, but it assists the implementation in
-- closing file handles as early as possible. It is an error to use the
-- argument in any way after making this call.

fRelease     :: File -> IO ()

-- | Returns a new File value which is identical to the argument except
-- that calling fRelease on one does not affect the other.

fDup         :: File -> IO File

-- | Returns True if fRelease has not been called on the File value.

fIsValid     :: File -> IO Bool

-- | Reads from a file to a memory buffer. If the read extends beyond the
-- end of the file, the extra buffer space is filled with zeroes and the
-- return value is the number of octets which actually came from the file.
-- Otherwise the return value is the same as the length argument.

fReadBuf     :: File -> FilePos -> BlockLength -> Ptr Word8 -> IO BlockLength

-- | Writes to a file from a memory buffer.

fWriteBuf    :: File -> FilePos -> BlockLength -> Ptr Word8 -> IO ()

-- | Returns the current size of the file.

fGetSize     :: File -> IO FilePos

-- | If the size argument is less than the current file size, the file size
-- is reduced, destroying any octets beyond the new end of the file. If the
-- size argument is greater than the current file size, the file may or may
-- not be increased in length. If it is increased, the contents of the file
-- beyond the old end of file are undefined.

fSetSize     :: File -> FilePos -> IO ()

fIsReadable  :: File -> IO Bool
fIsWritable  :: File -> IO Bool

-- * Layering channels on files

-- | Opens an input channel (octet source) which reads from the specified
-- file, starting at the specified offset. Effectively fDups the File
-- argument, so the original File value may be released at any later time
-- without affecting the channel.

fInputChannelFrom :: File -> FilePos -> IO InputChannel

-- | Opens an output channel (octet source) which writes to the specified
-- file, starting at the specified offset. Because input and output
-- channels may be buffered, the result of an fRead call on a file region

fOutputChannelFrom :: File -> FilePos -> IO OutputChannel

-- | Like fInputChannelFrom, but stops after reading the octet which
-- immediately precedes the second FilePos argument, or at end of file,
-- whichever comes first.

fInputChannelFromTo :: File -> FilePos -> FilePos -> IO InputChannel

-- * Standard channels

stdin :: InputChannel
stdout, stderr :: OutputChannel

-- * Input channel access functions

-- | Indicates that no more octets will be read from the InputChannel.
-- It is not necessary to call this function if all available octets
-- have already been read.

icRelease :: InputChannel -> IO ()

icGet     :: InputChannel -> IO Octet

icGetBuf  :: InputChannel -> Ptr a -> BlockLength -> IO BlockLength

icAtEnd   :: InputChannel -> IO Bool

-- | Returns the File associated with its argument, if any. May fail even
-- on a channel created with fInputChannel, since the channel is permitted
-- to release its internal File value on reaching end-of-input. May succeed
-- on a channel not created with fInputChannel, such as stdin. The caller
-- is responsible for releasing the returned File.

icTellFile :: InputChannel -> IO Maybe File

-- | Returns the current read offset in the underlying file, if any. May
-- succeed even if icTellFile fails. Always succeeds if the channel was
-- created on top of a File.

icTellPos :: InputChannel -> IO (Maybe FilePos)

icPeek    :: InputChannel -> IO Octet
icReady   :: InputChannel -> IO Bool

icGetBuffering :: InputChannel -> IO BufferMode
icSetBuffering :: InputChannel -> BufferMode -> IO ()

icIsTerminal   :: InputChannel -> IO Bool

-- | Read an InputChannel lazily as a list of octets. It is an error to
-- read from the InputChannel directly after this is called.

icLazyGetContents :: InputChannel -> IO [Octet]

-- * Output channel access functions

ocRelease  :: OutputChannel -> IO ()
ocPut      :: OutputChannel -> Octet -> IO ()
ocPuts     :: OutputChannel -> [Octet] -> IO ()
ocPutBuf   :: OutputChannel -> Ptr a -> BlockLength -> IO ()
ocTellFile :: OutputChannel -> IO (Maybe File)
ocTellPos  :: OutputChannel -> IO (Maybe FilePos)
ocGetBuffering :: OutputChannel -> IO BufferMode
ocSetBuffering :: OutputChannel -> BufferMode -> IO ()
ocFlush        :: OutputChannel -> IO ()
ocIsTerminal   :: OutputChannel -> IO Bool


-- Ben