Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-19 Thread Ketil Malde
David Owen [EMAIL PROTECTED] writes:

 Do you know if there are solutions to exersises available somewhere?
 Have you gone through the whole book, i.e. all the exercises?

 Unfortuantely I don't know of anywhere that the exercise answers can
 be found, even after some google searching.

Another option is posting the excercise to this list (or perhaps in
comp.lang.functional), along with your current effort at solving it.
(As this could look like a homework request, don't expect the direct
solution, but I think you will get some hints to nudge you in the
right direction.)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Math libraries for Haskell

2005-01-19 Thread Ketil Malde
Keean Schupke [EMAIL PROTECTED] writes:

 Can I request 2 types, one for dense (complete) matricies and
 another for sparse matricies?

...and maybe also put (!) in a class, so that it can be used as a general
indexing operator for all indexed data structures?  (Or is this
already possible?  I must admit I'm slightly lost in IArray, Ix,
HasBounds etc.) 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Re: Why is getArgs in the IO monad?

2005-01-19 Thread Keean Schupke
Of course both suggestions don't really change anything as:
   _main = do
  args - getArgs
  main args
(or the equivalent for implicit parameters) is all that is required... 
In a way
the implicit parameter approach makes it seem like a normal function...

Do you think implicit parameters could replace 
top-level-things-with-identity?

I hadn't really thought of it before (and I don't use implicit 
parameters much).

   Keean.
Ashley Yakeley wrote:
In article [EMAIL PROTECTED],
Keean Schupke [EMAIL PROTECTED] wrote:
 

Surely both requirements can be satisfied if the programs arguments are made
parameters of main:
main :: [String] - IO ()
   Keean.
   

Better yet, it should be an implicit parameter so as not to break 
existing programs.

 main :: (?args :: [String]) = IO ()
You could do the same with standard input and output.
 

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


[Haskell-cafe] tree with labeled edges as a monad

2005-01-19 Thread Andrew Pimlott
This is a have you seen this monad? post.  I was trying to construct a
search tree, and decided I wanted to do it in a monad (so I could apply
StateT and keep state as I explored the space).  I discovered that a
tree with labeled leaves is a monad, but I wanted to label internal
nodes, and such a tree (eg, Data.Tree.Tree) is not a monad (because it
can only have one result type).  Finally, I realized I could get a
similar effect by labeling the edges and the leaves with different
types:

data Tree l a = Leaf a | Branch [(l, Tree l a)]

instance Monad (Tree l) where
  return  = Leaf
  Leaf a = f= f a
  Branch c = f  = Branch [(l, t = f) | (l, t) - c]

You might use it as

turn = do
board - getBoard
move  - lift (Branch [(move, return move) | move - findMoves board])
applyMove move
turn

I found this quite pleasing, though I hadn't run across trees as monads
before.  Has anyone else found this useful?  Is it in a library
somewhere?

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


Re: [Haskell-cafe] tree with labeled edges as a monad

2005-01-19 Thread Ross Paterson
On Wed, Jan 19, 2005 at 01:40:06AM -0800, Andrew Pimlott wrote:
 This is a have you seen this monad? post.  I was trying to construct a
 search tree, and decided I wanted to do it in a monad (so I could apply
 StateT and keep state as I explored the space).  I discovered that a
 tree with labeled leaves is a monad, but I wanted to label internal
 nodes, and such a tree (eg, Data.Tree.Tree) is not a monad (because it
 can only have one result type).  Finally, I realized I could get a
 similar effect by labeling the edges and the leaves with different
 types:
 
 data Tree l a = Leaf a | Branch [(l, Tree l a)]
 
 instance Monad (Tree l) where
   return  = Leaf
   Leaf a = f= f a
   Branch c = f  = Branch [(l, t = f) | (l, t) - c]
 
 You might use it as
 
 turn = do
 board - getBoard
 move  - lift (Branch [(move, return move) | move - findMoves board])
 applyMove move
 turn
 
 I found this quite pleasing, though I hadn't run across trees as monads
 before.  Has anyone else found this useful?  Is it in a library
 somewhere?

More generally:

data Resumptions f a = Val a | Resume (f (Resumptions f a))

instance Functor f = Monad (Resumptions f) where
return  = Val
Leaf a = f= f a
Resume t = f  = Resume (fmap (= f) t)

An example is a model of the IO monad, with f instantiated to

data SysCall a
= GetChar (Char - a)
| PutChar Char a
| ...

This monad in turn is a special case of the monad transformer

newtype GR f m a = GR (m (Either a (f (GR f m a
unGR (GR x) = x

instance (Functor f, Monad m) = Monad (GR f m) where
return = GR . return . Left
GR r = f = GR (r = either (unGR . f)
  (return . Right . fmap (= f)))

which Moggi calls generalized resumptions in A syntactic approach
to modularity in denotational semantics, section 2.3.  This paper is
available on

http://www.disi.unige.it/person/MoggiE/publications.html

(It has some nice general monads, but is mostly impenetrable.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Top Level etc.

2005-01-19 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Keean Schupke [EMAIL PROTECTED] wrote:

 Do you think implicit parameters could replace 
 top-level-things-with-identity?
 
 I hadn't really thought of it before (and I don't use implicit 
 parameters much).

Yes, but I think people are clamouring for 
top-level-things-with-identity because they don't like implicit 
parameters. Not me, though.

I have been musing on the connection between data-types, modules, 
classes, and implicit parameters, and wondering if there might be some 
grand scheme to tie it all together. For instance, a module is very 
similar to class with no type parameters and all members defined. You'll 
notice that class members have different declared types inside and 
outside the class:

class C a where
   foo :: a - a -- inside

foo :: (C a) = a - a -- outside


Perhaps one could have top-level implicit parameters (or top-level 
contexts in general):

module (?myvar :: IORef Int) = Random where

  random :: IO Int -- inside
  random = do
i - readIORef ?myvar
...
writeIORef i'
return i'


module (?myvar :: IORef Int) = MyMain where
  import Random

  -- random :: IO Int -- also inside

  mymain :: IO ()
  mymain = do
...
i - random
...


module Main where
  import MyMain

  -- mymain :: (?myvar :: IORef Int) = IO () -- outside

  main = do
 var - newIORef 1   -- initialisers in the order you want
 let ?myvar = var in mymain

-- 
Ashley Yakeley, Seattle WA

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


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Benjamin Franksen
On Wednesday 19 January 2005 12:52, Ashley Yakeley wrote:
 I have been musing on the connection between data-types, modules,
 classes, and implicit parameters, and wondering if there might be
 some grand scheme to tie it all together. For instance, a module is
 very similar to class with no type parameters and all members
 defined. [...]

You will probably find this paper interesting: Wolfram Kahl and Jan 
Scheffczyk: Named Instances for Haskell Type Classes, 
http://www.informatik.uni-bonn.de/~ralf/hw2001/4.pdf

I wonder if their (conservative) extensions have ever been contemplated 
for inclusion in one of the standard Haskell implementations.

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


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Keean Schupke
I may have got this wrong, but I think you can do named instances 
without any extensions,
by using datatypes and fundeps:

data Instance0
data Instance1
instance0 :: Instance0
instance0 = undefined
instance1 :: Instance1
instance1 = undefined
class Named a b | a - b
   test :: a - b - b
instance Named Instance0 Int
   test _ a = a + a
instance Named Instance1 Float
   test _ a = a * a
test instance0 1
test instance1 1.5
   Keean.
Benjamin Franksen wrote:
You will probably find this paper interesting: Wolfram Kahl and Jan 
Scheffczyk: Named Instances for Haskell Type Classes, 
http://www.informatik.uni-bonn.de/~ralf/hw2001/4.pdf
 

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


RE: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Simon Marlow
On 19 January 2005 09:45, Ben Rudiak-Gould wrote:

 Glynn Clements wrote:
 
  Ben Rudiak-Gould wrote:
  
  GHC really needs non-blocking
  I/O to support its thread model, and memory-mapped I/O always
  blocks. 
  If, by blocks, you mean that execution will be suspended until the
  data has been read from the device into the buffer cache, then Unix
  non-blocking I/O (i.e. O_NONBLOCK) also blocks.
 
 Okay, my ignorance of Posix is showing again. Is it currently the
 case, then, that every GHC thread will stop running while a disk read
 is in progress in any thread? Is this true on all platforms?

It's true on Unix-like systems, I believe.  Even with -threaded.  It
might not be true on Win32.

 (By the way, are the GHC folks aware that the description of Win32 I/O
 at [2] is wrong? It seems to assume that ReadFile doesn't return until
 the buffer is full.)

I don't think that description corresponds with the implementation, but
then I'm not terribly familiar with that part of the code.  It doesn't
get used when -threaded is on.

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread William Lee Irwin III
On 19 January 2005 09:45, Ben Rudiak-Gould wrote:
 Okay, my ignorance of Posix is showing again. Is it currently the
 case, then, that every GHC thread will stop running while a disk read
 is in progress in any thread? Is this true on all platforms?

On Wed, Jan 19, 2005 at 01:39:05PM -, Simon Marlow wrote:
 It's true on Unix-like systems, I believe.  Even with -threaded.  It
 might not be true on Win32.

How does forkOS fit into this picture? It's described in the
documentation as allowing concurrent execution of system calls
and other activity by other threads.


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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Keean Schupke
Simon Marlow wrote:

Okay, my ignorance of Posix is showing again. Is it currently the
case, then, that every GHC thread will stop running while a disk read
is in progress in any thread? Is this true on all platforms?
   

It's true on Unix-like systems, I believe.  Even with -threaded.  It
might not be true on Win32.
 

I think this is not true on linux, where a thread is just a process created
with special flags to keep the same fds and memory.
As threads on linux are scheduled like processes, one thread blocking should
not affect the others?
(As an alternative there is always the AIO library)
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Simon Marlow
On 19 January 2005 13:50, William Lee Irwin III wrote:

 On 19 January 2005 09:45, Ben Rudiak-Gould wrote:
 Okay, my ignorance of Posix is showing again. Is it currently the
 case, then, that every GHC thread will stop running while a disk
 read is in progress in any thread? Is this true on all platforms?
 
 On Wed, Jan 19, 2005 at 01:39:05PM -, Simon Marlow wrote:
 It's true on Unix-like systems, I believe.  Even with -threaded.  It
 might not be true on Win32.
 
 How does forkOS fit into this picture? It's described in the
 documentation as allowing concurrent execution of system calls
 and other activity by other threads.

forkOS doesn't fix this.  It forks another OS thread which can be used
to make concurrent foreign calls, if they are not marked unsafe.
However, the standard I/O library, in -threaded mode, does read like
this:

- non-blocking, unsafe, read() to see what's there
- if read() would block, then hand off to another
  Haskell thread which does select() on all the outstanding
  IO requests.

This scheme is just for efficiency.  We could (and used to) just call
safe read() for every read - that would give you the right concurrency
with -threaded, but unfortunately you'd really notice the difference if
you had 1000s of threads all doing IO, because each one would need its
own OS thread.  The current scheme is rather snappy (even snappier than
non-threaded, as it happens).

You can always do System.Posix.fileRead to get around it.

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Keean Schupke
Why not use a thread-pool, and a safe call to read, provided there is 
an OS thread available,
defaulting to unsafe if no thread is available... You could make the 
thread pool size an argument...

   Keean.
Simon Marlow wrote:
On 19 January 2005 13:50, William Lee Irwin III wrote:
 

On 19 January 2005 09:45, Ben Rudiak-Gould wrote:
   

Okay, my ignorance of Posix is showing again. Is it currently the
case, then, that every GHC thread will stop running while a disk
read is in progress in any thread? Is this true on all platforms?
   

On Wed, Jan 19, 2005 at 01:39:05PM -, Simon Marlow wrote:
   

It's true on Unix-like systems, I believe.  Even with -threaded.  It
might not be true on Win32.
 

How does forkOS fit into this picture? It's described in the
documentation as allowing concurrent execution of system calls
and other activity by other threads.
   

forkOS doesn't fix this.  It forks another OS thread which can be used
to make concurrent foreign calls, if they are not marked unsafe.
However, the standard I/O library, in -threaded mode, does read like
this:
   - non-blocking, unsafe, read() to see what's there
   - if read() would block, then hand off to another
 Haskell thread which does select() on all the outstanding
 IO requests.
This scheme is just for efficiency.  We could (and used to) just call
safe read() for every read - that would give you the right concurrency
with -threaded, but unfortunately you'd really notice the difference if
you had 1000s of threads all doing IO, because each one would need its
own OS thread.  The current scheme is rather snappy (even snappier than
non-threaded, as it happens).
You can always do System.Posix.fileRead to get around it.
Cheers,
	Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


Re: [Haskell-cafe] GHC for .NET?

2005-01-19 Thread Andre Santos
Hi,
[only now I am catching up with the messages from the
beginning of the year from haskell-cafe...]
Simon Peyton-Jones wrote:
  * Andre Santos and his colleagues at  UFPE in Brazil are working on a
.NET back end,
that generates CLR IL, though I don't know where they are up to.
  * GHC.Net would be extra attractive if there was a Visual Studio
integration for GHC.
Substantial progress on this has been made in 2004 by Simon
Marlow, Krasimir
Angelov, and Andre Santos and colleagues.
We are indeed involved in these two projects,
with support from Microsoft's academic/research initiatives.
Due to various delays we have not progressed much in the
implementation of the .NET back end for GHC itself,
but we will be working a lot more on this from now on.
We have a group (with some graduate and postgraduate students)
who have studied compilation alternatives and some
of the existing implementations, and we are
working now on a prototype implementation to start with,
still focusing only on compiling the Haskell standard to IL/.NET.
Then we should roughly try to follow the steps SimonPJ described.
For the Visual Studio integration with GHC we have released a preview
about a month ago with partial results of the efforts by
SimonM/Krasimir/us, and we should also keep this development going.
Although it currently has no dependencies with .NET code generation,
it will be really nice if we manage to integrate the two, eventually.
But even the use of the IDE itself (with tooltips, on-the-fly
type checking, code completion etc.)
should be quite an improvement for the whole Haskell
programming/teaching experience.
cheers,
Andre.
___
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 integer is distinguished from a
Unix signal, 

RE: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Simon Marlow
We do use a thread pool.  But you still need as many OS threads as there
are blocked read() calls, unless you have a single thread doing select()
as I described.  BTW our Haskell Workshop paper from last year describes
this stuff:

  http://www.haskell.org/~simonmar/papers/conc-ffi.ps.gz

Cheers,
Simon

On 19 January 2005 15:07, Keean Schupke wrote:

 Why not use a thread-pool, and a safe call to read, provided there
 is an OS thread available,
 defaulting to unsafe if no thread is available... You could make the
 thread pool size an argument...
 
 Keean.
 
 Simon Marlow wrote:
 
 On 19 January 2005 13:50, William Lee Irwin III wrote:
 
 
 
 On 19 January 2005 09:45, Ben Rudiak-Gould wrote:
 
 
 Okay, my ignorance of Posix is showing again. Is it currently the
 case, then, that every GHC thread will stop running while a disk
 read is in progress in any thread? Is this true on all platforms?
 
 
 On Wed, Jan 19, 2005 at 01:39:05PM -, Simon Marlow wrote:
 
 
 It's true on Unix-like systems, I believe.  Even with -threaded. 
 It might not be true on Win32. 
 
 
 How does forkOS fit into this picture? It's described in the
 documentation as allowing concurrent execution of system calls
 and other activity by other threads.
 
 
 
 forkOS doesn't fix this.  It forks another OS thread which can be
 used to make concurrent foreign calls, if they are not marked
 unsafe. However, the standard I/O library, in -threaded mode, does
 read like this: 
 
- non-blocking, unsafe, read() to see what's there
- if read() would block, then hand off to another
  Haskell thread which does select() on all the outstanding  
 IO requests. 
 
 This scheme is just for efficiency.  We could (and used to) just call
 safe read() for every read - that would give you the right
 concurrency with -threaded, but unfortunately you'd really notice
 the difference if you had 1000s of threads all doing IO, because
 each one would need its own OS thread.  The current scheme is rather
 snappy (even snappier than non-threaded, as it happens). 
 
 You can always do System.Posix.fileRead to get around it.
 
 Cheers,
  Simon
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Duncan Coutts
On Wed, 2005-01-19 at 15:06 +, Keean Schupke wrote:
 Why not use a thread-pool, and a safe call to read, provided there is 
 an OS thread available,
 defaulting to unsafe if no thread is available... You could make the 
 thread pool size an argument...

If it's just a question of speed then the fastest IO system is the
variety that GHC uses now: a single OS thread that multiplexes all IO
requests using a select loop.

The fastest network servers work this way too. Hundreds of network
clients with a single OS thread using multiplexed non-blocking IO and
using epoll (or an equivalent). I don't think there are many that use
many threads to do async IO. Probably the only servers that use the
thread pool IO style seriously are things like Oracle.

If you have more than one CPU you would want more than one OS thread.
The number of threads should scale with the number of CPUs not the
number of Haskell threads that want to do IO.

Duncan

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Keean Schupke
Duncan Coutts wrote:
If it's just a question of speed then the fastest IO system is the
variety that GHC uses now: a single OS thread that multiplexes all IO
requests using a select loop.
 

But what about the continuing computation... we do not want
the fastest IO system, but we want the program to comlete the
fastest... So ideally we want 2 threads!
One runs the Haskell code that is not waiting for IO. (IE other
Haskell threads)... The other runs a select loop as you suggest!
This way the number of threads is fixed (2) and execution never
'blocks' for IO. (Simon, what about this scheme?)
If you have more than one CPU you would want more than one OS thread.
The number of threads should scale with the number of CPUs not the
number of Haskell threads that want to do IO.
 

I completely agree with this, but obviously I would suggest 1 thread
per CPU, (maybe 2 including a garbage collector) plus an additional
thread on the CPU attached to the IO bus to do IO.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Keean Schupke
Simon Marlow wrote:
On 19 January 2005 16:49, Keean Schupke wrote:
 

But what about the continuing computation... we do not want
the fastest IO system, but we want the program to comlete the
fastest... So ideally we want 2 threads!
One runs the Haskell code that is not waiting for IO. (IE other
Haskell threads)... The other runs a select loop as you suggest!
This way the number of threads is fixed (2) and execution never
'blocks' for IO. (Simon, what about this scheme?)
   

This is what GHC does, if I understand you correctly.  The thread
running select() does so in its own OS thread, while another OS thread
runs the Haskell code.  As long as you use -threaded, that is.  Oh, and
before GHC 6.4 it was done a different way - the scheduler used to do
the select() between running Haskell threads.
Cheers,
	Simon
 

So this means even though the IO calls block, the other Haskell threads
(when run with -threaded) keep running?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tree with labeled edges as a monad

2005-01-19 Thread Iavor Diatchki
Hi,
This is a hey that's cool post :-)
I have seen both of those separately --- the generalized resumptions monad,
and the IO (and others) monad written in continuation passing style,
but never realized that the one was an instance of the other.
It is neat how the basic operations are separated from the sequencing.
Does anyone know how related (it seems somewhat related) is all that to the
recent work by Plotkin and Power on deriving monad implementations
from their operations?
-Iavor


 More generally:
 
 data Resumptions f a = Val a | Resume (f (Resumptions f a))
 
 instance Functor f = Monad (Resumptions f) where
 return  = Val
 Leaf a = f= f a
 Resume t = f  = Resume (fmap (= f) t)
 
 An example is a model of the IO monad, with f instantiated to
 
 data SysCall a
 = GetChar (Char - a)
 | PutChar Char a
 | ...

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


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Jorge Adriano Aires
 Perhaps one could have top-level implicit parameters (or top-level
 contexts in general):

 module (?myvar :: IORef Int) = Random where

Hi!
I suggested something very similar to this some months ago, syntax and all. 
Nice to see I'm not the only one thinking along this lines.
http://www.mail-archive.com/haskell%40haskell.org/msg14884.html


 module Main where
   import MyMain

   -- mymain :: (?myvar :: IORef Int) = IO () -- outside

   main = do
  var - newIORef 1   -- initialisers in the order you want
  let ?myvar = var in mymain

By then I also suggest that maybe we could also bind the implicit on import,  
something like:

 module (?par :: Parameter) = A where 
 ...

 module B where
 import A -- simple, ?par unbound
 import qualified A as Ak where ?par = k -- ?par bound to k
 import qualified A as Am where ?par = m -- ?par bound to m

Seemed fine as long as the parameters didn't depend on the imported modules. 
But on hindsight, making an import depend on valued defined in the body of 
the module is probably quite clumsy, unfortunately (right?). Still, 

 import qualified A as Ak where ?par = 1
or 
 import qualified A as Ak where ?par = newIORef
or even 
 import C(k)
 import qualified A as Ak where ?par = k 

Doesn't sound that bad though. 

J.A.

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


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Benjamin Franksen
On Wednesday 19 January 2005 14:31, Keean Schupke wrote:
 I may have got this wrong, but I think you can do named instances
 without any extensions,
 by using datatypes and fundeps:

 data Instance0
 data Instance1

 instance0 :: Instance0
 instance0 = undefined

 instance1 :: Instance1
 instance1 = undefined

 class Named a b | a - b
 test :: a - b - b
 instance Named Instance0 Int
 test _ a = a + a
 instance Named Instance1 Float
 test _ a = a * a


 test instance0 1
 test instance1 1.5

Sure you can. However, the extension presented in the paper goes way beyond 
this (while still being conservative). For instance, named instances can be 
defined for standard Haskell98 classes, they don't need special class 
definitions as in your example. For a given class, standard unnamed instances 
may be used together with additional named instances. Another benefit of the 
proposal is that it slves a number of problems regarding multi-parameter 
classes quite elegantly.

But the reason why I mentioned the paper was that it offers a lot of insight 
into exactly what Ashley Yakeley was thinking about. Citing again:
 I have been musing on the connection between data-types, modules, 
 classes, and implicit parameters, and wondering if there might be some  
 grand scheme to tie it all together.

Neither I nor the authors claim that their proposal is the ultimate grand 
scheme, yet. Still I think there are very interesting ideas in there that 
should be considered for experimental implementation or further research.

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Glynn Clements

Keean Schupke wrote:

 Okay, my ignorance of Posix is showing again. Is it currently the
 case, then, that every GHC thread will stop running while a disk read
 is in progress in any thread? Is this true on all platforms?
 
 It's true on Unix-like systems, I believe.  Even with -threaded.  It
 might not be true on Win32.
 
 I think this is not true on linux, where a thread is just a process created
 with special flags to keep the same fds and memory.
 
 As threads on linux are scheduled like processes, one thread blocking should
 not affect the others?

That should be true of all POSIX-like thread implementations
(including Linux, whose threads aren't quite POSIX-compliant, e.g. in
regard to signal handling, but aren't that far off).

Essentially, blocking system calls only block the calling kernel
thread.

OTOH, if you are implementing multiple user-space threads within a
single kernel thread, if that kernel thread blocks, all of the
user-space threads within it will be blocked.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Glynn Clements

Simon Marlow wrote:

 We do use a thread pool.  But you still need as many OS threads as there
 are blocked read() calls, unless you have a single thread doing select()
 as I described.

How does the select() help? AFAIK, select() on a regular file or block
device will always indicate that it is readable, even if a subsequent
read() would have to read the data from disk.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Benjamin Franksen
On Wednesday 19 January 2005 21:20, Jorge Adriano Aires wrote:
  Perhaps one could have top-level implicit parameters (or top-level
  contexts in general):
 
  module (?myvar :: IORef Int) = Random where

 I suggested something very similar to this some months ago, syntax and all.
 Nice to see I'm not the only one thinking along this lines.

Please note that implicit parameters -- at least as currently implemented in 
GHC -- have a number of severe problems. A good summary was given by Ben 
Rudiak-Gould in 
http://www.mail-archive.com/haskell%40haskell.org/msg15595.html (although in 
a different context):

 [...] In a program with implicit parameters:
  
  * Beta conversion no longer preserves semantics.
 
  * The monomorphism restriction is no longer a restriction: it sometimes
  silently changes the meaning of a program. 
  
  * Adding type signatures for documentation is no longer safe, since they
  may silently change the behavior of the program. 
 
  * It's not even safe in general to add a signature giving the same type
  that the compiler would infer anyway: there are (common) cases in which
  this too changes the program's meaning. I ran into this quite by accident
  the first time I tried to use implicit parameters, and it was enough to
  scare me away from ever trusting them again.

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


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Keean Schupke
Benjamin Franksen wrote:
Neither I nor the authors claim that their proposal is the ultimate grand 
scheme, yet. Still I think there are very interesting ideas in there that 
should be considered for experimental implementation or further research.
 

But thats interesting isn't it. If one extension can be defined in terms
of the other, then only one of the extensions is necessary. There is
obviously some connection between functional dependancies and
named instances. Maybe there is a better mechanism that both
can be defined in terms of?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugs vs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Glynn Clements

Ben Rudiak-Gould wrote:

  GHC really needs non-blocking
  I/O to support its thread model, and memory-mapped I/O always blocks.
  
  If, by blocks, you mean that execution will be suspended until the
  data has been read from the device into the buffer cache, then Unix
  non-blocking I/O (i.e. O_NONBLOCK) also blocks.
 
 Okay, my ignorance of Posix is showing again. Is it currently the case, 
 then, that every GHC thread will stop running while a disk read is in 
 progress in any thread?

The kernel thread which called read() will be blocked. If GHC threads
are userspace threads running within a single kernel thread, then they
will all block. If GHC uses multiple kernel threads, the other kernel
threads will continue to run.

 Is this true on all platforms?

Some platforms (but, AFAIK, not linux) allow asynchronous I/O on
regular files. NT has overlapped I/O, which is essentially the same
thing.

 There are two ways of reading from a file/stream in Win32 on NT. One is 
 asynchronous: the call returns immediately and you receive a 
 notification later that the read has completed. The other is synchronous 
 but almost-nonblocking: it returns as much data as is available, and 
 the entire contents of a file is considered always available. But it 
 always returns at least one byte, and may spend an arbitrary amount of 
 time waiting for that first byte. You can avoid this by waiting for the 
 handle to become signalled; if it's signalled then a subsequent ReadFile 
 will not block indefinitely.
 
 Win32's synchronous ReadFile is basically the same as Posix's (blocking) 
 read. For some reason I thought that Win32's asynchronous ReadFile was 
 similar to Posix's non-blocking read, but I gather from [1] that they're 
 completely different.

They're similar, but not identical. Traditionally, Unix non-blocking
I/O (along with asynchronous I/O, select() and poll()) were designed
for slow streams such as pipes, terminals, sockets etc. Regular
files and block devices are assumed to return the data immediately.

Essentially, for slow streams, you have to wait for the data to arrive
before it can be read, so waiting may take an indefinite amount of
time. For fast streams, the data is always available, you just
have to wait for the system call to give it to you.

IOW, the time taken to read from a block device is amortised into the
execution time of the system call, rather than being treated as a
delay.

Also, even with blocking I/O, slow streams only block if no data is
available. If less data is available than was requested, they will
usually return whatever is available rather than waiting until they
have the requested amount. Non-blocking I/O only affects the case
where no data is available.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Benjamin Franksen
On Wednesday 19 January 2005 21:48, Keean Schupke wrote:
 Benjamin Franksen wrote:
 Neither I nor the authors claim that their proposal is the ultimate grand
 scheme, yet. Still I think there are very interesting ideas in there that
 should be considered for experimental implementation or further research.

 But thats interesting isn't it. If one extension can be defined in terms
 of the other, then only one of the extensions is necessary. There is
 obviously some connection between functional dependancies and
 named instances. Maybe there is a better mechanism that both
 can be defined in terms of?

Any idea? I'll propose you for the next Nobelprize in Programming Language 
Design ;--)

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


Re: [Haskell-cafe] Re: Hugs vs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Marcin 'Qrczak' Kowalczyk
Glynn Clements [EMAIL PROTECTED] writes:

 They're similar, but not identical. Traditionally, Unix non-blocking
 I/O (along with asynchronous I/O, select() and poll()) were designed
 for slow streams such as pipes, terminals, sockets etc. Regular
 files and block devices are assumed to return the data immediately.

Indeed. Reading from a slow block device is also not interruptible by
a signal; a signal usually causes reading from a pipe/socket/terminal
to fail with EINTR.

There is no non-blocking interface to various functions like readdir,
mkdir, stat etc.

OTOH close() is interruptible.

It seems that the only way to parallelize them is to use a separate
OS thread.

gethostbyname, gethostbyaddr, getservbyname and getservbyport are
mostly superseded by getaddrinfo and getnameinfo. They are all
blocking and non-interruptible by signals (they restart their loops
on receiving EINTR from low-level calls).

Glibc provides getaddrinfo_a which is non-blocking (implemented using
pthreads). Contrary to documentation it's not interruptible by a
signal (its implementation expects pthread_cond_wait to fail with
EINTR which is not possible) and it's not cancellable in a useful way
(the interface allows for cancellation, which may nevertheless answer
that it cannot be cancelled, and the glibc implementation is able to
cancel a request only if it hasn't yet started being processed by the
thread pool). There is no non-blocking counterpart of getnameinfo.

Since asynchronous name resolution is quite important, implementation
of my language uses pthreads and getaddrinfo / getnameinfo, if
pthreads are available. For simplicity I just make one thread per
request.

A tricky API to parallelize is waitpid. Pthreads are supposed to be
able to wait for child processes started by any thread, but according
to man pages this was broken in Linux before version 2.4. Fortunately
it's easy to avoid blocking other threads indefinitely without OS
threads if we agree to waste CPU time (not CPU cycles), such that a
thread waiting for a process takes as much time as if it was doing
some useful work. Because waitpid *is* interruptible by signals. So it
will either finish, or the timer signal will interrupt it and control
can be passed to other threads.

Leaving the timer signal interrupting syscalls can break libraries
which don't expect EINTR. For example the Python runtime doesn't
handle EINTR specially and it is translated to a Python exception.

-- 
   __( 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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-19 Thread Marcin 'Qrczak' Kowalczyk
Glynn Clements [EMAIL PROTECTED] writes:

 We do use a thread pool.  But you still need as many OS threads as there
 are blocked read() calls, unless you have a single thread doing select()
 as I described.

 How does the select() help? AFAIK, select() on a regular file or block
 device will always indicate that it is readable, even if a subsequent
 read() would have to read the data from disk.

It doesn't help if we don't want I/O requests to delay one another,
and not only avoiding delay of execution of pure Haskell code.

BTW, poll is generally preferred to select. The maximum fd supported
by select may be lower than the maximum fd supported by the system.
And the interface of poll allows the cost to be proportional to the
number of descriptors rather than to the highest descriptor.

The timeout is specified in microseconds for select and in milliseconds
for poll, but on Linux the actual resolution is the clock tick in both
cases anyway (usually 1ms or 10ms).

It's probably yet better to use epoll than poll. The difference is
that with epoll you register fds using separate calls, and you don't
have to provide them each time you wait (and the kernel doesn't have
to scan the array each time). So it scales better to a large number of
threads which perform I/O. It's available in Linux 2.6.

Caveat: before Linux 2.6.8 epoll had a memory leak in the kernel
because of a reference counting bug (0.5kB per epoll_create call,
which means 0.5kB of physical memory lost per starting a program
which waits for I/O using epoll).

poll is in Single Unix Spec, epoll is Linux-specific.

poll and epoll both take the timeout in the same format, but they
interpret it differently: poll sleeps at least the given time (unless
a fd is ready or a signal arrives), while epoll rounds it up to a
whole number of clock ticks and then sleeps between this time and one
tick shorter. I was told that this is intentional because it allows
to sleep until the next clock tick by specifying the timeout of 1ms
(a timeout of 0ms means to not sleep at all).

Accurate sleeping requires to measure the time by which poll/epoll can
make the timeout longer (it's 1 tick for epoll and 2 ticks for poll),
subtract this time from the timeout passed to them, add 1ms, and sleep
the remaining time by busy waiting calling gettimeofday interspersed
with poll/epoll with no timeout. gettimeofday() is accurate to
microseconds, it asks some clock chip instead of relying on the timer
interrupt only.

-- 
   __( 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


[Haskell-cafe] Re: Top Level etc.

2005-01-19 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Benjamin Franksen [EMAIL PROTECTED] wrote:

 Please note that implicit parameters -- at least as currently implemented in 
 GHC -- have a number of severe problems. A good summary was given by Ben 
 Rudiak-Gould in 
 http://www.mail-archive.com/haskell%40haskell.org/msg15595.html (although in 
 a different context):

This is mostly ambiguity due to missing type-signatures, isn't it? 
That's not so severe in my view. But maybe the compiler can issue a 
warning in such cases.

-- 
Ashley Yakeley, Seattle WA

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


[Haskell-cafe] Re: Top Level etc.

2005-01-19 Thread Jim Apple
Benjamin Franksen wrote:
Please note that implicit parameters -- at least as currently implemented in 
GHC -- have a number of severe problems.
Does anyone have examples of these? This one scares the foo out of me:
* It's not even safe in general to add a signature giving the same type
that the compiler would infer anyway
Jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe