[Haskell-cafe] Objects in Haskell
Benjamin Franksen
benjamin.franksen at bessy.de
Sun Nov 28 18:39:03 EST 2004
[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
-------------- next part --------------
-- 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
More information about the Haskell-Cafe
mailing list