Re: [Haskell-cafe] Execution Contexts

2004-11-28 Thread Ian . Stark
On Sat, 27 Nov 2004, Benjamin Franksen wrote:
 I would think that with ACIO we have a nice mathematical
 characterization for the IO actions that would be safe even at the
 top-level. (Safe meaning mainly that we do not open a can-of-worms
 with regard to execution order.) I don't know how easy or hard it is to
 prove of a certain IO action that is in fact in ACIO.

Hard, because it depends on observational equivalence of IO effects, and
for that you need a semantics for the RealWorld.

Maybe a better way to treat it is that whereas doing an IO action puts it
in an execution trace at a specific point, doing an ACIO action is simply
perform this some time, maybe, if required.  Giving something like
newUnique an ACIO type indicates that semantics is sufficient; whereas for
readIORef it typically isn't, and you want the stronger guarantee of an IO
type.

 This breaks down as soon as the IO action does a forkIO.

Isn't sharing global variables the correct semantics for forkIO ?
That explicitly creates a 'lightweight' thread, which shares execution
context with its invoker.

I agree that forkOS, with its own local context, is harder.  I suspect
that, yes, as soon as you want to have more than one execution context
simultaneously, then you need to manage them.  For which XIO seems
to do the job.

Ian

--
Ian Stark   http://www.ed.ac.uk/~stark
LFCS, School of Informatics, The University of Edinburgh, Scotland
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Execution Contexts

2004-11-28 Thread Ian . Stark
Ben,

On Sat, 27 Nov 2004, Benjamin Franksen wrote (apropos ACIO topdecls):
 ... a highly controversial new language feature.

The language feature is easily done, and just what has been happening all
along:

  type ACIO = IO

  declare :: ACIO a - a

  {-# NOINLINE declare #-}
  declare e = unsafePerformIO e

All 'affine central' does is give a label to one particular idiomatic use
of IO.  The controversial part would be wading through libraries arguing
over what things were ACIO.

OK, I admit it would be nice if the compiler would manage everything, use
- syntax, and take advantage of affine central actions being
well-behaved.  But not vital.

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


Re: [Haskell-cafe] Execution Contexts

2004-11-28 Thread Benjamin Franksen
On Sunday 28 November 2004 13:53, Keean Schupke wrote:
 ... here is an example object
 in actuall Haskell code using the HList library...

  point = do
x - newIORef 0
returnIO $ mutableX .=. x
 .*. getX .=. readIORef x
 .*. moveD .=. (\d - modifyIORef x ((+) d))
 .*. emptyRecord

 And here's the object in use:
  myFirstOOP = do
   p - point
   p # getX = print
   p # moveD $ 3
   p # getX = print

 As you can see no lifting or awkwardness involved... the syntax looks
 very much like the OCaml example it was ported from.

Very nice. This would be enough for single threaded programs and as long as 
the local state is simple.

I think it would get quite awkward as soon as you want to provide

- more mutable members
- synchronized access + asynchronous methods

(i.e. _reactive_ objects)

I am ready to be proved wrong, though.

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


Re: [Haskell-cafe] Haskore Wiki

2004-11-28 Thread Shae Matijs Erisson
Henning Thielemann [EMAIL PROTECTED] writes:

  I also like to point to my private work on Haskore. It includes
 bug-fixes, a more fine-grained modularization, better support for infinite
 music data, 

I've used Haskore before, but I wasn't able to figure out how to make infinte
compositions. I'd like to try turning a lorenz fractal into music, could you
point me to an example of such an infinite song? Can you actually play such a
thing from Haskore?

Thanks,
-- 
Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said:
You could switch out the unicycles for badgers, and the game would be the same.

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


[Haskell-cafe] Objects in Haskell

2004-11-28 Thread Benjamin Franksen
[this has drifted off-topic quite a bit, so new subject]

On Sunday 28 November 2004 17:29, Benjamin Franksen wrote:
 I think it would get quite awkward as soon as you want to provide

 - more mutable members
 - synchronized access + asynchronous methods

 (i.e. _reactive_ objects)

 I am ready to be proved wrong, though.

I couldn't wait so I proved myself wrong myself ;)

Since I didn't get the extensible records example to compile, I translated it 
to normal Haskell records. The state is still only one mutable Int but the 
object is fully reactive. The code is attached and I do not find it awkward 
(although the generic object API could still be improved).

One problem remains: to preserve reactivity, the programmer must make sure 
that methods don't execute IO actions that may block indefinitely. 
Unfortunately there is no way in Haskell to enforce this, because 
(indefinitely) blocking IO actions have the same type as non-blocking ones. 
Too late to change that, I guess...

Btw, here is one of my all-time favourite quotes:


The view of indefinite blocking as a transparent operational property dates 
back to the era of batch-oriented computing, when interactivity was a term 
yet unheard of, and buffering operating systems had just become widely 
employed to relieve the programmer from the intricacies of synchronization 
with card-readers and line-printers. Procedure-oriented languages have 
followed this course ever since, by maintaining the abstraction that a 
program environment is essentially just a subroutine that can be expected to 
return a result whenever the program so demands. Selective method filtering 
is the object-oriented continuation of this tradition, now interpreted as 
``programmers are more interested in hiding the intricacies of method-call 
synchronization, than preserving the intuitive responsiveness of the object 
model''.

Some tasks, like the standard bounded buffer, are arguably easier to implement 
using selective disabling and queuing of method invocations. But this help is 
deceptive. For many clients that are themselves servers, the risk of becoming 
blocked on a request may be just as bad as being forced into using polling 
for synchronization, especially in a distributed setting that must take 
partial failures into account. Moreover, what to the naive object implementor 
might look like a protocol for imposing an order on method invocations, is 
really a mechanism for reordering the invocation-sequences that have actually 
occurred. In other words, servers for complicated interaction protocols 
become disproportionately easy to write using selective filtering, at the 
price of making the clients extremely sensitive to temporal restrictions that 
may be hard to express, and virtually impossible to enforce.


(see http://www.cs.chalmers.se/~nordland/ohaskell/rationale.html)

Cheers,
Ben
-- Timber-like reactive objects
import Control.Concurrent
import Data.IORef

-- fake OO notation
infixl 1 #
o # f = f o

-- an object is represented by its message queue
newtype Object = O (Chan Message)

-- a message is just an IO action
type Message = IO ()

-- method types
type Action = IO ()   -- asynchronous method; caller continues (no result)
type Request a = IO a -- synchronous method; caller waits for result

-- construct an action
action :: Object - IO () - Action
action (O ch) act = writeChan ch act

-- construct a request
request :: Object - IO a - Request a
request (O ch) req = do
  m - newEmptyMVar
  writeChan ch (do
r - req
putMVar m r)
  takeMVar m

-- construct an object
newObject :: IO Object
newObject = do
  ch - newChan
  msgs - getChanContents ch
  forkIO $ sequence_ msgs
  return (O ch)

-- the braindead moving point example

-- point interface
data IPoint = IPoint {
getX :: IO Int,
move :: Int - IO ()
  }

-- construct a point
point = do
  state - newIORef 0
  self - newObject
  return IPoint {
  move = \d - action self $ modifyIORef state ((+) d),
  getX = request self $ readIORef state
}

main = do
  p - point
  p # getX = print
  p # move $ 3
  p # getX = print
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe