Re: [Haskell-cafe] I/O interface

2005-01-19 Thread Keean Schupke
Have you read the OOHaskell paper?
   http://homepages.cwi.nl/~ralf/OOHaskell/
This shows how to encode many OO idioms in Haskell, without any extensions
(beyond those that GHC already supports)... Here's some sample code
(from the Shapes.hs example) to give you a flavor of it:
A constructor function:
   rectangle x y width height self
 = do
 super <- shape x y self
 w <- newIORef width
 h <- newIORef height
 returnIO $
  getWidth  .=. readIORef w
  .*. getHeight .=. readIORef h
  .*. setWidth  .=. (\neww -> writeIORef w neww)
  .*. setHeight .=. (\newh -> writeIORef h newh)
  .*. draw  .=.
  do
 putStr  "Drawing a Rectangle at:(" <<
 self # getX << ls "," << self # getY <<
 ls "), width " << self # getWidth <<
 ls ", height " << self # getHeight <<
 ls "\n"
  .*. super
And an example of some objects in use:
   myShapesOOP =
 do
  -- set up array of shapes
  s1 <- mfix (rectangle (10::Int) (20::Int) 5 6)
  s2 <- mfix (circle (15::Int) 25 8)
  let scribble :: [Shape Int]
  scribble = [narrow s1, narrow s2]
   

  -- iterate through the array
  -- and handle shapes polymorphically
  mapM_ (\shape -> do
  shape # draw
  (shape # rMoveTo) 100 100
  shape # draw)
scribble
   

  -- call a rectangle specific function
  arec <- mfix (rectangle (0::Int) (0::Int) 15 15)
  arec # setWidth $ 30
  arec # draw
   Regards,
   Keean.
Marcin 'Qrczak' Kowalczyk wrote:
Haskell provides only:
- algebraic types (must specify all "subtypes" in one place),
- classes (requires foralls which limits applicability:
 no heterogeneous lists, I guess no implicit parameters),
- classes wrapped in existentials, or records of functions
 (these two approaches don't support controlled downcasting,
 i.e. "if this is a regular file, do something, otherwise do
 something else").
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I/O interface

2005-01-19 Thread Marcin 'Qrczak' Kowalczyk
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes:

> Yes, this is a problem. In my original proposal InputStream and
> OutputStream were types, but I enthusiastically embraced Simon M's
> idea of turning them into classes. As you say, it's not without its
> disadvantages.

This is my greatest single complaint about Haskell: that it doesn't
support embedding either OO-style abstract supertypes, or dynamnic
typing with the ability to use polymorphic operations on objects that
we don't know the exact type.

The Dynamic type doesn't count for the latter because you must guess
the concrete type before using the object. You can't say "it should be
something implementing class Foo, I don't care what, and I only want
to use Foo's methods with it".

Haskell provides only:
- algebraic types (must specify all "subtypes" in one place),
- classes (requires foralls which limits applicability:
  no heterogeneous lists, I guess no implicit parameters),
- classes wrapped in existentials, or records of functions
  (these two approaches don't support controlled downcasting,
  i.e. "if this is a regular file, do something, otherwise do
  something else").

The problem manifests itself more when we add more kinds of streams:
transparent compression/decompression, character recoding, newline
conversion, buffering, userspace /dev/null, concatenation of several
input streams, making a copy of data as it's passed, automatic
flushing of a related output stream when an input stream is read, etc.

A case similar to streams which would benefit from this is DB
interface. Should it use separate types for separate backends? Awkward
to write code which works with multiple backends. Should it use a
record of functions? Then we must decide at the beginning the complete
set of supported operations, and if one backend provides something
that another doesn't, it's impossible to write code which requires
the first backend and uses the capability (unless we decide at the
beginning about all possible extensions and make stubs which throw
exceptions in cases it's not supported). I would like to mix these
two approaches: if some code uses only operations supported by all
backends, then it's fully polymorphic, and when it starts using
specific operations, it becomes limited. Without two completely
different designs for these cases. I don't know how to fit it into
Haskell's type system. This has led me to exploring dynamic typing.

> Again, to try to avoid confusion, what you call a "seekable file" the
> library calls a "file", and what you call a "file" I would call a
> "Posix filehandle".

So the incompleteness problem can be rephrased: the interface doesn't
provide the functionality of open() with returns an arbitrary POSIX
filehandle.

> By the same token, stdin is never a file, but the data which appears
> through stdin may ultimately be coming from a file, and it's sometimes
> useful, in that case, to bypass stdin and access the file directly.
> The way to handle this is to have a separate stdinFile :: Maybe File.

And a third stdin, as POSIX filehandle, to be used e.g. for I/O
redirection for a process.

> As for openFile: in the context of a certain filesystem at a certain
> time, a certain pathname may refer to
>
>   * Nothing
>   * A directory
>   * A file (in the library sense); this might include things like
> /dev/hda and /dev/kmem
>   * Both ends of a (named) pipe
>   * A data source and a data sink which are related in some
> qualitative way (for example, keyboard and screen, or stdin and stdout)
>   * A data source only
>   * A data sink only
>   * ...
>
> How to provide an interface to this zoo?

In such cases I tend to just expose the OS interface, without trying
to be smart. This way I can be sure I don't make anything worse than
it already is.

Yes, it probably makes portability harder. Suitability of this
approach depends on our goals: either we want to provide a nice and
portable abstraction over the basic functionality of all systems,
or we want to make everything implementable in C also implementable
in Haskell, including a Unix shell.

Perhaps Haskell is in the first group. Maybe its goal is to invent
an ideal interface to the computer's world, even if this means doing
things differently than everyone else. It's hard to predict beforehand
how far in being different we can go without alienating users.

For my language I'm trying to do the second thing. I currently
concentrate on Unix because there are enough Windows-inspired
interfaces in .NET, while only Perl and Python seem to care about
providing a rich access to Unix API from a different language than C.

I try to separate interfaces which should be portable from interfaces
to Unix-specific things. Unfortunately I have never programmed for
Windows and I can make mistakes about which things are common to
various systems and which are not. Time will tell and will fix this.

Obviously I'm not copying the Unix interface literally. A file is
distinguished from an integer, and an int

RE: [Haskell-cafe] I/O interface

2005-01-19 Thread Simon Marlow
On 18 January 2005 00:27, Ben Rudiak-Gould wrote:

> Marcin 'Qrczak' Kowalczyk wrote:
> 
>  >Convenience. I'm worried that it uses separate types for various
>  >kinds of streams: files, pipes, arrays (private memory), and
>  sockets. >Haskell is statically typed and lacks subsumption. This
>  means that >even though streams are unified by using a class, code
>  which uses >a stream of an unknown kind must be either polymorphic
>  or use >existential quantification.
> 
> Yes, this is a problem. In my original proposal InputStream and
> OutputStream were types, but I enthusiastically embraced Simon M's
> idea of turning them into classes. As you say, it's not without its
> disadvantages.

I recognised this problem, which is why TextInputStream and
TextOutputStream are existential wrappers around streams.  Most clients
will be using the Text streams, so they won't suffer from the
polymorphism problem.

However, we could also provide a non-overloaded version using one of
Ben's solutions:

> I see several possibilities here.
> 
> * We could adopt Avery Lee's suggestion (from the discussion in
> 2003) to use field labels instead of methods. Advantages: InputStream
> and OutputStream behave more like their OOP equivalents, with no loss
> of extensibility. Disadvantages: potentially less efficient (no
> specialization possible); loses some static type information.

Unfortunately GHC isn't nearly as good at optimising records as it is at
optimising type class overloading.  Of course, type class overloading is
just a special case of polymorphic records, but there you go.

> * We could use a single type for all input and output streams in
> the standard library, but retain the type classes also.
> 
> * We could provide existential wrappers:
> 
>   data IStream = (InputStream a) => MkIStream !a
>   instance InputStream IStream where ...

This one gets my vote.

BTW, Marcin: the library in the prototype implementation differs
somewhat from the version of the interface in the Haddock docs.  The
docs were written before I started hacking on the prototype.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I/O interface

2005-01-17 Thread Duncan Coutts
On Mon, 2005-01-17 at 16:27 -0800, Ben Rudiak-Gould wrote:
> Marcin 'Qrczak' Kowalczyk wrote:
> 
>  >Convenience. I'm worried that it uses separate types for various
>  >kinds of streams: files, pipes, arrays (private memory), and sockets.
>  >Haskell is statically typed and lacks subsumption. This means that
>  >even though streams are unified by using a class, code which uses
>  >a stream of an unknown kind must be either polymorphic or use
>  >existential quantification.
> 
> Yes, this is a problem. In my original proposal InputStream and 
> OutputStream were types, but I enthusiastically embraced Simon M's idea 
> of turning them into classes. As you say, it's not without its 
> disadvantages.
> 
> I see several possibilities here.
> 
> * We could adopt Avery Lee's suggestion (from the discussion in 
> 2003) to use field labels instead of methods. Advantages: InputStream 
> and OutputStream behave more like their OOP equivalents, with no loss of 
> extensibility. Disadvantages: potentially less efficient (no 
> specialization possible); loses some static type information.

I've often thought it would be nice to have a class and it's most
general instance, a record with the same fields as the class has
methods. It would be even better if they could share the same name, eg:

class IStream s where
  read :: s -> ...

data IStream = IStream {
read :: ...
  }

instance IStream IStream where
  read s = read s --the field selector not the class method

Obviously each instance of the IStream class can be converted to an
IStream record (loosing type information) which is useful for
heterogeneous collections of streams, and other "interface programming"
techniques.

This technique is perhaps a middle ground, it's a tad more complex that
just having a single type for streams but it allows code which does not
want to know to use a single type while allowing for static typing in
other cases where it is desired for safety or for better performance by
specialising.

A downside (apart from naming issues) is that while there is an
automatic conversion IStream data type -> IStream class instance, there
is no automatic conversion the other way round. Compare this with Java
interfaces for example, a Java IStream interface is like our IStream
data type, but there is automatic conversion from the types implementing
the interface to the interface type itself. In Haskell we normally go
for the more strongly typed interfaces (Haskell classes) rather than the
more dynamic interfaces (record of functions) so the language supports
the former more naturally than the latter (eg automatic 'conversion'
when accessing an object through a class interface).

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I/O interface

2005-01-17 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote:
>Convenience. I'm worried that it uses separate types for various
>kinds of streams: files, pipes, arrays (private memory), and sockets.
>Haskell is statically typed and lacks subsumption. This means that
>even though streams are unified by using a class, code which uses
>a stream of an unknown kind must be either polymorphic or use
>existential quantification.
Yes, this is a problem. In my original proposal InputStream and 
OutputStream were types, but I enthusiastically embraced Simon M's idea 
of turning them into classes. As you say, it's not without its 
disadvantages.

I see several possibilities here.
   * We could adopt Avery Lee's suggestion (from the discussion in 
2003) to use field labels instead of methods. Advantages: InputStream 
and OutputStream behave more like their OOP equivalents, with no loss of 
extensibility. Disadvantages: potentially less efficient (no 
specialization possible); loses some static type information.

   * We could use a single type for all input and output streams in the 
standard library, but retain the type classes also.

   * We could provide existential wrappers:
 data IStream = (InputStream a) => MkIStream !a
 instance InputStream IStream where ...
A nice thing about the last approach is that it supports dynamic 
downcasting:

   case (x :: IStream) of
 MkIStream x ->
   case (Data.Dynamic.cast x :: UArrayInputStream) of
 Just x -> (getUArray x, getCurrentIndex x)
 Nothing -> ...
>Completeness. Unless File{Input,Output}Stream uses {read,write}()
>rather than file{Read,Write}, openFile provides only a subset of
>the functionality of open(): it works only with seekable files,
>e.g. not with "/dev/tty".
>
>What is the type of stdin/stdout? They may be devices or pipes
>(not seekable), regular files (seekable), sockets...
Simon M's current interface is incomplete, but the concept is fine.
Again, to try to avoid confusion, what you call a "seekable file" the 
library calls a "file", and what you call a "file" I would call a "Posix 
filehandle". Roughly. It's hard to be precise because "file" is such a 
heavily overloaded term. (For example, is "/dev/tty" a file? Is the 
(major,minor) device number it might correspond to on a particular 
filesystem at a particular moment a file? Is the integer that's returned 
from open("/dev/tty", ...) a file? Is the tty device itself a file? I 
think you've used "file" in all four senses.)

When I talk about a stream, I mean one end of a unidirectional pneumatic 
tube. If it's the ingoing end, you stick some data in the tube and it's 
carried away. If it's the outgoing end, you wait for some data to arrive 
and then take it. Tubes all look the same. No pneumatic tube is a 
storage device, but you may happen to know that it leads to a Frobozz 
Magic Storage Device at the other end.

By the same token, stdin is never a file, but the data which appears 
through stdin may ultimately be coming from a file, and it's sometimes 
useful, in that case, to bypass stdin and access the file directly. The 
way to handle this is to have a separate stdinFile :: Maybe File.

As for openFile: in the context of a certain filesystem at a certain 
time, a certain pathname may refer to

 * Nothing
 * A directory
 * A file (in the library sense); this might include things like 
/dev/hda and /dev/kmem
 * Both ends of a (named) pipe
 * A data source and a data sink which are related in some qualitative 
way (for example, keyboard and screen, or stdin and stdout)
 * A data source only
 * A data sink only
 * ...

How to provide an interface to this zoo?
The dynamic-typing approach is to return some sort of Thing with a 
complicated interface which is approximately the union of the interfaces 
for each thing in the above list. Unsupported methods fail when called. 
This is roughly what Posix does, except that directories are a special 
case, and Nothing is very special (as perhaps it should be, but I'm not 
sure).

The Haskell approach is, I guess, to use an algebraic datatype, e.g.
   data FilesystemObject
 = Directory Directory
 | File File
 | InputOutput PosixInputStream PosixOutputStream
 | Input PosixInputStream
 | Output PosixOutputStream
Here I'm using "Posix*Stream" for all streams backed by Posix 
filehandles. I'm unsure whether NoSuchPath should be in there too.

You might say that this is annoyingly complicated. My first reaction is 
"tough--it's exactly as complicated as the reality it models". But there 
should presumably be helper functions of types FilesystemObject->IStream 
and FilesystemObject->OStream.

The other complication is that Posix makes you specify access rights 
when you look up a path in the filesystem. This makes no sense, but it's 
something we have to live with.

So I'd argue for replacing openFile with something like
   data FilesystemObject = ...
   openPath :: FilePath -> IOMode -> IO FilesystemObject
   filesystemInputStream :: Files

Re: [Haskell-cafe] I/O interface

2005-01-16 Thread Keean Schupke
Marcin 'Qrczak' Kowalczyk wrote:
Convenience. I'm worried that it uses separate types for various
kinds of streams: files, pipes, arrays (private memory), and sockets.
Haskell is statically typed and lacks subsumption. This means that
even though streams are unified by using a class, code which uses
a stream of an unknown kind must be either polymorphic or use
existential quantification.
 

Or uses specialise pragmas to provide concrete implementations
for a polymorphic function.
Exploiting the advantages of mapped files for stream I/O
http://www.cs.toronto.edu/pub/reports/csrg/267/267.ps
   

The advantage of reducing copying between buffers is lost in Haskell:
file{Read,Write} use a buffer provided by the caller instead of giving
a buffer for the caller to examine or fill.
 

Eh? Surely that just depends on the API. The BlockIO library does
exactly this (passes the blocks to a user provided callback function)
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] I/O interface (was: Re: Hugs vs GHC)

2005-01-16 Thread Marcin 'Qrczak' Kowalczyk
John Meacham <[EMAIL PROTECTED]> writes:

> I was thinking of it as a better implementation of a stream interface
> (when available).

I'm not convinced that the stream interface
(http://www.haskell.org/~simonmar/io/System.IO.html) works at all,
i.e. whether it's complete, implementable and convenient.

Convenience. I'm worried that it uses separate types for various
kinds of streams: files, pipes, arrays (private memory), and sockets.
Haskell is statically typed and lacks subsumption. This means that
even though streams are unified by using a class, code which uses
a stream of an unknown kind must be either polymorphic or use
existential quantification.

Completeness. Unless File{Input,Output}Stream uses {read,write}()
rather than file{Read,Write}, openFile provides only a subset of
the functionality of open(): it works only with seekable files,
e.g. not with "/dev/tty".

What is the type of stdin/stdout? They may be devices or pipes
(not seekable), regular files (seekable), sockets...

Note that even when they are regular files, emulating stream I/O
in terms of either pread/pwrite or mmap does not yield the correct
semantics of sharing the file pointer between processes. If we have
a shell script which runs Haskell programs which write to stdout,
it should be possible to redirect the output of the script as a whole.

> Exploiting the advantages of mapped files for stream I/O
>  http://www.cs.toronto.edu/pub/reports/csrg/267/267.ps

The advantage of reducing copying between buffers is lost in Haskell:
file{Read,Write} use a buffer provided by the caller instead of giving
a buffer for the caller to examine or fill.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe