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

Simon Marlow simonmar@microsoft.com
Wed, 6 Aug 2003 12:51:58 +0100


Following all the suggestions in this thread, I've written out a new proposal.  I hope I've managed to resolve most of the comments
people had, or otherwise left comments in place, if that's not the case please complain.

To summarise, the primary innovations here are:

  - Streams are layered on top of various kinds of underlying I/O
    objects, and have a set of uniform operations provided by the
    Stream, InputStream and OutputStream classes.  (no-one thought
    that using type classes was a bad idea, so I've left them in).

  - Streams can be layered on top of arrays.  Files can be mapped
    into memory and exposed as arrays.  (I thinnk this part is
    particularly nice).

There's a Haddock-processed version of the file here:

   http://www.haskell.org/~simonmar/io/System.IO.html

Cheers,
	Simon

-- | The naming is all subject to change, we're interested in
-- functionality first.

module System.IO (
  -- * Buffers
  Buffer,  withBuffer,
  ImmutableBuffer,
  -- $buffers

  -- * Files
  File, FileInputStream, FileOutputStream,
  FileOffset,
  openFile, closeFile,
  fileSize, fileSetSize,
  fileRead, fileGet, fileWrite,  
  fileInputStream, fileOutputStream,
  mapFile,

  -- * MappedFiles
  MappedFile,
  -- $mappedfiles

  -- * Pipes
  PipeInputStream, PipeOutputStream,
  createPipe,

  -- * Arrays as streams
  ArrayInputStream, ArrayOutputStream,
  iarrayInputStream,
  marrayInputStream, marrayOutputStream,

  -- * Sockets

  -- | The socket support won't live in System.IO, it will be in
  -- "Network.Socket" as before.

  Socket, SocketInputStream, SocketOutputStream,
  socketGetInputStream, socketGetOutputStream,
  -- $sockets

  -- * Streams
  Stream(..),
  InputStream(..),
  OutputStream(..),

 ) where

-- -----------------------------------------------------------------------------
-- Buffers

-- | A mutable array of bytes that can be passed to foreign functions.
data Buffer
instance MArray Buffer Word8 IO
withBuffer :: Buffer -> (Ptr Word8 -> IO a) -> IO a

-- | An immutable array of bytes
data ImmutableBuffer
instance IArray ImmutableBuffer Word8

-- $buffers
-- The idea is that Buffer should be useful for text encoding\/decoding.
--
-- Implementation notes: on GHC, 'Buffer' could be implemented by 'IOUArray', 
-- using a pinned 'ByteArray#' as the underlying object, so that the buffer
-- address can be passed to foreign functions.
--
-- (a 'StorableArray' would do for Buffer, but an 'IOUArray' will be more
-- efficient).

-- ----------------------------------------------------------------------------
-- Files

data File  -- a mutable array of bytes, with some access permissions
data FileInputStream
data FileOutputStream
instance Stream FileInputStream where {}
instance Stream FileOutputStream where {}
instance InputStream FileInputStream where {}
instance OutputStream FileOutputStream where {}

type FileOffset = Integer

openFile    :: FilePath -> IOMode -> IO File
closeFile   :: File -> IO ()

fileSize    :: File -> IO Integer
fileSetSize :: File -> Integer -> IO ()

fileRead    :: File -> FileOffset -> Integer -> Buffer -> IO ()
fileGet     :: File -> FileOffset -> Integer -> IO ImmutableBuffer
fileWrite   :: File -> FileOffset -> Integer -> Buffer -> IO ()

-- TODO: what if a file refers to a FIFO?
fileInputStream  :: File -> FileOffset -> IO FileInputStream
fileOutputStream :: File -> FileOffset -> IO FileOutputStream

mapFile     :: File -> FileOffset -> Integer -> MapMode -> IO MappedFile

-- ---------------------------------------------------------------------------
-- Mapped files

-- | A portion of a 'File' mapped directly into memory.  The data can
-- be read and written using the array operations, and streams to the
-- data can be created using 'marrayInputStream' and 'marrayOutputStream'.
data MappedFile
instance MArray MappedFile Word8 IO

-- $mappedfiles
-- A 'MappedFile' might be implemented as a 'StorableArray', with a
-- 'ForeignPtr' inside it.  The finalizer can unmap the file.

-- -----------------------------------------------------------------------------
-- Pipes

data PipeInputStream
data PipeOutputStream
instance Stream PipeInputStream
instance Stream PipeOutputStream
instance InputStream PipeInputStream
instance OutputStream PipeOutputStream

createPipe :: IO (PipeInputStream,PipeOutputStream)

-- -----------------------------------------------------------------------------
-- Arrays

-- | An input stream created from an array.
data ArrayInputStream
instance Stream ArrayInputStream
instance InputStream ArrayInputStream

-- | An output stream created from an array.
data ArrayOutputStream
instance Stream ArrayOutputStream
instance OutputStream ArrayOutputStream

-- | Creates an 'ArrayInputStream' from an immutable array
iarrayInputStream  :: (Ix i, IArray a Word8) => a i Word8 -> i 
	-> ArrayInputStream

-- | Creates an 'ArrayInputStream' from a mutable array
marrayInputStream  :: (Ix i, MArray a Word8 IO) => a i Word8 -> i
	-> ArrayInputStream

-- | Creates an 'ArrayOutputStream' from a mutable array
marrayOutputStream :: (Ix i, MArray a Word8 IO) => a i Word8 -> i
	-> ArrayOutputStream

-- -----------------------------------------------------------------------------
-- Sockets

data Socket
data SocketInputStream
data SocketOutputStream
instance Stream SocketInputStream
instance Stream SocketOutputStream
instance InputStream SocketInputStream
instance OutputStream SocketOutputStream

socketGetInputStream :: Socket -> SocketInputStream
socketGetOutputStream :: Socket -> SocketOutputStream

-- $sockets
-- Input and output streams for a socket can be closed
-- independently. 
--
-- Each socket has only one pair of input\/output
-- streams, hence these functions are pure.

-- -----------------------------------------------------------------------------
-- Streams

class Stream s where
	closeStream	   :: s -> IO ()

	-- | Note: objections have been raised about this method, and
	-- are still to be resolved.  It doesn't make as much sense
	-- for output streams as it does for input streams.
	isEOS	      	   :: s -> IO Bool

-- On Buffering:
-- Not all streams are buffered; for example, there's no point in buffering an
-- array stream, or a mapped file.  However, using a separate class
-- for buffered streams won't work: you couldn't write a function that
-- behaved differently when given an unbuffered stream or a buffered
-- stream.

	-- | Sets the buffering mode on the stream.  Returns 'True' if
	-- the buffereing mode was set, or 'False' if it wasn't.  If the
 	-- stream does not support buffereing, it may return 'False' here.
	setBufferMode 	:: s -> BufferMode -> IO Bool

	-- | Returns the current buffering mode for a stream.  On a 
	-- stream that does not support buffering, the result will always
	-- be 'NoBuffering'.
	getBufferMode 	:: s -> IO BufferMode

	-- | Flushes the buffer to the operating system for an output
	-- buffer, or discards buffered data for an input buffer.
	flush	   	:: s -> IO ()

	-- | Flushes the buffered data as far as possible, even to the
	-- physical media if it can.  It returns 'True' if the data
	-- has definitely been flushed as far as it can go: to the 
	-- disk for a disk file, to the screen for a terminal, and so on.
	sync		:: s -> IO Bool

class InputStream s where
	streamGet	   :: s -> IO Word8
	streamReadBuffer   :: s -> Integer -> Buffer -> IO ()
	streamGetBuffer    :: s -> Integer -> IO ImmutableBuffer
	streamGetContents  :: s -> IO [Word8]

	-- | Gets any data which can be read without blocking.
	streamGetAvailable :: s -> IO [Word8]

class OutputStream s where
	streamPut         :: s -> Word8 -> IO ()
	streamPuts        :: s -> [Word8] -> IO ()
	streamWriteBuffer :: s -> Integer -> Buffer -> IO ()
	streamPutBuffer   :: s -> Integer -> ImmutableBuffer -> IO ()

-- -----------------------------------------------------------------------------
-- Notes

{-
 Parameterise InputStream over the element type too, so we can
 combine InputStream and TextInputStream?  NO: uses multiparam type
 classes.

 Naming: maybe put all the stream ops in one module, and use qualfied names
 eg. Stream.close, Stream.setBuffering etc.

 From Ashley Yakely:
  3. I note all the class members have types of the form "s -> a" each for 
  some "a" not dependent on "s". This means streams might be a candidate 
  for data structures:
  
    data InputStream m = {
       isStream :: Stream m, 
       streamGet :: m Word8,
       streamReadBuffer :: Integer -> Buffer -> IO ()
       ...
    }
  
  I'm not sure which is preferable however. Data-structure inheritance has 
  to be done by hand (except see point 9., it might only be a close 
  function), and they don't allow default implementations (yet).
-}