[Haskell-cafe] Non-blocking for reactive programs (was: Objects in Haskell)

2004-11-29 Thread Graham Klyne
At 00:39 29/11/04 +0100, Benjamin Franksen wrote:
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...
I was somewhat intrigued by this comment.  Maybe I'm missing the point or 
simply too detached from the thrust of this thread to make any sense here, 
but wondered if anything really needs to be changed to be able to express 
this idea of non-blocking IO.

Suppose we define a new type, say NBIO, which, like IO, allows any 
interaction with the external world, but with the proviso that it never 
blocks (I shalln't attempt to try and define exactly what this means, but 
hope that the intent is clear).  A key function associated with this type 
would have type:
forall a. NBIO a - IO a

Thus any non-blocking I/O activity can be implemented in NBIO, and its 
IO-equivalent is always available.  But not the converse, of course.

...
I think I now see the problem:  while functions can be implemented in NBIO, 
and thereby convey an intended guarantee to the caller, there's no way I 
can see for the Haskell type system to stop a programmer to write a 
function of this type that actually uses (but does not return a value from) 
an IO value.  Without this, how can facilities like Debug.Trace be provided?

But then again, if no value from an IO is ever actually used or referenced 
outside the IO code, doesn't lazy evaluation mean that there's never any 
need to evaluate the value within IO?

Now getting hopelessly out of my depth, but interested in any comments you 
may have...

#g
--
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)

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help!

2004-11-29 Thread balarcon

Hi,
I'm a computer´s student and have some problems with a work I have to do.
My teacher has an application written in Haskell(with GUI) and he wants I work
on Visual Studio.net to make a GUI in C# and its buttons have to call his
Haskell'application . I'm very disoriented and help'needed.Please!!

Betty



This message was sent using IMP, the Internet Messaging Program.

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


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread George Russell
(indexing with TypeRep)
 This is yet another incidence where Robert Will's ByMaps would be very useful
In fact GHC at least *already* generates a unique integer for each TypeRep.
A good idea, since it means comparisons can be done in unit time.
Thus indexing can be done trivially using this integer as a hash function.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread Benjamin Franksen
On Monday 29 November 2004 11:35, George Russell wrote:
 (indexing with TypeRep)

   This is yet another incidence where Robert Will's ByMaps would be
   very useful

 In fact GHC at least *already* generates a unique integer for each
 TypeRep. A good idea, since it means comparisons can be done in unit
 time. Thus indexing can be done trivially using this integer as a
 hash function.

Yes, I have seen this in the code, too. The Ord and Typeable instances 
should be trivial.

[off topic:]

There was a recent discussion about allowing to derive an instance from 
anywhere at the top-level, and not only in the type definition. This is 
one more example where such a feature would be very useful.

Another related example is the class Typeable itself. It has been noted 
by others that the current interface is not type safe, since mkTyCon 
gets an arbitrary string as argument. (Unfortunately this means that 
GlobalVariables.hs and ExecutionContext.hs aren't really type safe 
either).

Typeable would be completely safe if the only way to declare instances 
would be to derive them, but this is only practical if it can be done 
from anywhere outside the data type definition.

Can anyone think of a situation where adding a derived instance to an 
abstract data type breaks one of its invariants?

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


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-29 Thread George Russell
Benjamin wrote (snipped):
 Typeable would be completely safe if the only way to declare instances
 would be to derive them, but this is only practical if it can be done
 from anywhere outside the data type definition.
Unfortunately this would also outlaw some legitimate uses of Typeable.
In particular, I think you can only derive Typeable for a type
constructor of type (*).  GHC has recently added Typeable1,Typeable2,...
which are classes of type constructors of kind *-*, *-*-* and so on, up
to 6 arguments I think, and these can be derived, which is a great help.
But there are still kinds this does not include; for example (*-*)-*,
which is an example of a type constructor I actually used where I wanted
an instance of Typeable.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help!

2004-11-29 Thread Keith Wansbrough
 Hi,
 I'm a computer´s student and have some problems with a work I have to do.
 My teacher has an application written in Haskell(with GUI) and he wants I work
 on Visual Studio.net to make a GUI in C# and its buttons have to call his
 Haskell'application . I'm very disoriented and help'needed.Please!!

Option 1: have your C# application send faked .NET GUI messages
(button clicked, text entered, and so on) to the Haskell GUI, using
SendMessage or whatever it's called.

Option 2: on the Haskell side, implement a little textual command
language that allows you to drive the Haskell app; connect it to a
socket; arrange that the C# app sends the commands to the socket.

Option 3: use the Haskell FFI to connect to a C wrapper that
implements whatever interface you like; use the .NET native support to
talk to that interface.

Option 4: compile Haskell to IL using the (experimental) switch on the
GHC compiler.

What does your teacher want you to do?

Reply to the list, please, not to me only.

--KW 8-)



-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell-cafe] emtpy fundep LHS

2004-11-29 Thread Robert Dockins
Keean Schupke wrote:
Martin Sulzmann wrote:
Well, if there's only instance which is not exported, then you can
use functional dependencies.
Assume
class C a
instance ... = C t
Internally, use
class C a | - a
instance ... = C t
 

The cases I was looking at had more than one instance, but thats
cool! (I didn't realise  - a was valid syntax without a LHS for the 
arrow.
I didn't either.  That is cool.
Oleg has written quite a bit about using fundeps to close classes. Surely
you can export this as well - any attempt to add another instance will
conflict with the fundep (- a) which effectively says there can only be
one instance as all the LHS will overlap (all being the empty set)?
Indeed, it seems to me that one could bootstrap arbitrary closed classes 
from a class with the (- a) fundep and multiparameter type classes. 
(code follows).  Then, I should be able to prove some properties of the 
MyNum class (and type-level programs using it) without worrying about 
users coming along behind and adding instances.  Does this work?  Is 
this what you had in mind?

module FunkyNats
( MyNum (...)
, Zero
, Succ
, Twice
-- don't export Close
) where
-- The unit closed class
data Close
class Closed a | - a
instance Closed Close
-- a closed class build from Closed
class (Closed c) = MyNum c a
-- the class members
data Zero
data Succ a
data Twice a
-- requires access to Close to make instances
instance MyNum Close Zero
instance (MyNum a) = MyNum Close (Succ a)
instance (MyNum a) = MyNum Close (Twice a)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] emtpy fundep LHS

2004-11-29 Thread Keean Schupke
Robert Dockins wrote:
Indeed, it seems to me that one could bootstrap arbitrary closed 
classes from a class with the (- a) fundep and multiparameter type 
classes. (code follows).  Then, I should be able to prove some 
properties of the MyNum class (and type-level programs using it) 
without worrying about users coming along behind and adding 
instances.  Does this work?  Is this what you had in mind?

module FunkyNats
( MyNum (...)
, Zero
, Succ
, Twice
-- don't export Close
) where
-- The unit closed class
data Close
class Closed a | - a
instance Closed Close
-- a closed class build from Closed
class (Closed c) = MyNum c a
-- the class members class (Closed c) = MyNum c a
data Zero
data Succ a
data Twice a
-- requires access to Close to make instances
instance MyNum Close Zero
instance (MyNum a) = MyNum Close (Succ a)
instance (MyNum a) = MyNum Close (Twice a)
Yes this seems to require access to the 'Close' constructor
in order to add an instance to MyNum.
Unfortunatley you also would need access to close to use an
instance, but because the second parameters are all distinct,
you can add the following fundep to the class:
class (Closed c) = MyNum c a | a - c
Now, you can call the class without access to the Close constructor:
instance (MyNum c n,MyNum c m) = instance Sum n m ...
Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] not possible with monad transformers ?

2004-11-29 Thread Pavel Zolnikov
Hi, I have been playing with Maybe and Output monad transformers 
and realized that I cannot make the following work nicely:

 foo a b = do
   output before
   r - (liftM2(+)) a b
   when r == Nothing $ output error
   return r

As soon as computation produces Nothing, I am loosing ability to do any 
output. I think what I need is not wrapping one monad into another with 
transformer; I need some sort of monad combiner:

 newtype MC m1 m2 = MC (m1 a, m2 b)

So I could execute both of monads in parallel. But I have no idea 
how to express this or even if this is doable at all. Any comments?

Thanks,
Pavel.

P.S. Here is summary of what I tried with transformers so far:

Lets say I have following monad transformers:

 newtype MaybeMonadT m a = MMT  (m a)

 newtype OuptutMonadT m o a = OMT (m a, o)

And I am trying to use following monads:

 type M1 a = MaybeMonadT OutputM a
 type M2 a = OuptutMonadT Maybe String a

Now, they both wont quite work in the following example:

 foo a b = do
   output before
   r - (liftM2(+)) a b
   when r == Nothing $ output error
   return r


In case of M1, as soon as I get Nothing in r, computation will stop 
and return without any output gathered.

In case of M2, as soon as I get Nothing in r, computation will stop 
and return only with output gathered so far. That is 
 output error 
will never be called.


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


[Haskell-cafe] Re: OO in Haskell

2004-11-29 Thread Keean Schupke
Benjamin Franksen wrote:
I still have problems. They are probably due to a wrong definition of the 
operator (#). Note that (#) is nowhere defined inside the HList sources, so I 
assumed an inverse application aoperator. This is my program now:
 

No, # is the record selection operator from the HList based records.
infixr 9 #
m # field = m .!. field
Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: OO in Haskell

2004-11-29 Thread Benjamin Franksen
On Monday 29 November 2004 21:47, Keean Schupke wrote:
 Benjamin Franksen wrote:
 I still have problems. They are probably due to a wrong definition of the
 operator (#). Note that (#) is nowhere defined inside the HList sources,
  so I assumed an inverse application operator. This is my program now:

 No, # is the record selection operator from the HList based records.

 infixr 9 #
 m # field = m .!. field

Of course, stupid me. Ok, I changed that. Still won't compile. I post only the 
first of four type errors (they are all about 40 lines long; note that the 
inferred type below is almost longer than the complete test program).

TestObject.hs:16:
No instances for (HFind' b4
 (Proxy GetX)
 (HCons (Proxy GetX) (HCons (Proxy MoveD) HNil))
 n1,
  HEq (Proxy GetX) (Proxy MutableX) b4,
  HFind' b3
 (Proxy MoveD)
 (HCons (Proxy GetX) (HCons (Proxy MoveD) HNil))
 n,
  HEq (Proxy MoveD) (Proxy MutableX) b3,
  HLookupByHNat n
(HCons (IORef a) (HCons (IO a) (HCons (a 
- IO ()) HNil)))
(a1 - IO t),
  HLookupByHNat n1
(HCons (IORef a) (HCons (IO a) (HCons (a 
- IO ()) HNil)))
(IO a2),
  HOr b2 HFalse HFalse,
  HEq (Proxy GetX) (Proxy MoveD) b2,
  HOr b b' HFalse,
  HOr b1 HFalse b',
  HEq (Proxy MutableX) (Proxy MoveD) b1,
  HEq (Proxy MutableX) (Proxy GetX) b)
  arising from use of `.*.' at TestObject.hs:16
In the second argument of `($)', namely
`(mutableX .=. x)
 .*. ((getX .=. (readIORef x))
  .*. ((moveD .=. (\ d - modifyIORef x ((+) d))) .*. 
emptyRecord))'
In the result of a 'do' expression:
returnIO
$ ((mutableX .=. x)
   .*. ((getX .=. (readIORef x))
.*. ((moveD .=. (\ d - modifyIORef x ((+) d))) .*. 
emptyRecord)))
In the definition of `point':
point = do
  x - newIORef 0
  returnIO
  $ ((mutableX .=. x)
 .*. ((getX .=. (readIORef x))
  .*. ((moveD .=. (\ d - modifyIORef x ((+) d))) .*. 
emptyRecord)))


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


Re: [Haskell-cafe] Haskore Wiki (really Haskore T-shirt)

2004-11-29 Thread Fritz Ruehr
Henning and others who are interested in Haskore might want to check 
out the Haskore-themed T-shirt available from CafePress:

http://www.cafepress.com/haskore.13482964
Note that the 8 laws of polymorphic temporal media appear on the rear 
side of the shirt: just click on the View Larger Images link to see 
them. (I could also cut a cheaper, one-sided version of the shirt if 
anyone is interested.)

I made this design for Paul Hudak without realizing that there would be 
a big market for Haskore shirts (so I am pleasantly surprised).

As always, we here at Haskell-Themed Merchandise, Inc. make no profit 
on the merchandise we sell at cost through CafePress.

  --  Fritz Ruehr
PS: There are also some Haskell-themed infant/toddler clothing items 
that haven't made it onto the Haskell merchandise page yet, see 
http://www.cafepress.com/HaskellBoys and 
http://www.cafepress.com/HaskellGirls. HTMI's marketing department 
has been duly chastised for the delays :) .

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


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IOinitializers

2004-11-29 Thread John Meacham
On Mon, Nov 29, 2004 at 03:09:53PM -, Simon Peyton-Jones wrote:
 |  In fact GHC at least *already* generates a unique integer for each
 |  TypeRep. A good idea, since it means comparisons can be done in unit
 |  time. Thus indexing can be done trivially using this integer as a
 |  hash function.
 | 
 | Yes, I have seen this in the code, too. The Ord and Typeable instances
 | should be trivial.
 
 Take care here.  There is no guarantee that the unique number generated
 will be the same in each run.  So if you have Ord Typeable, this program
 may give unpredictable results:
 
 main = print (typeOf True  typeOf 'x')
 
 This unfortunate observabilty of an ordering (or hash value) that is
 needed only for efficient finite maps, is very annoying.  I wish I knew
 a way round it.  As it is we can pick
   a) expose Ord/Hash, but have unpredictable results
   b) not have Ord/Hash, but have inefficient maps

I thought it would be good to have two Ord classes, one to give the
natural ordering (Ord) if one exists, and one to give the most efficient
one for implementing maps/sets which has the side constraint that
nothing may observably depend on what the actual order is, just that it
is a valid total ordering. I have come across a few types where such a
distinction would have been nice to have. either because the ordering
was arbitrary so exposing it via 'Ord' seemed like a white lie to the
user or a much more efficient yet non-intuitive ordering was possible..

of course, the side condition here is pretty vauge. I don't know how to
enforce it within the type system, but it is a pretty straightforward
condition which I don't think would cause too much trouble in practice
to maintain.

John

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


Re: [Haskell-cafe] not possible with monad transformers ?

2004-11-29 Thread Mike Gunter


This:

  foo a b = do
output before 
let r = liftM2 (+) a b 
when (r == Nothing) $ output error 
return r -- ??? lift r

seems to address your complains, but I don't understand what you want
well enough to know if this is that.

mike

Pavel Zolnikov [EMAIL PROTECTED] writes:

 Hi, I have been playing with Maybe and Output monad transformers 
 and realized that I cannot make the following work nicely:

 foo a b = do
  output before
  r - (liftM2(+)) a b
  when r == Nothing $ output error
  return r

 As soon as computation produces Nothing, I am loosing ability to do any 
 output. I think what I need is not wrapping one monad into another with 
 transformer; I need some sort of monad combiner:

 newtype MC m1 m2 = MC (m1 a, m2 b)

 So I could execute both of monads ‘in parallel’. But I have no idea 
 how to express this or even if this is doable at all. Any comments?

 Thanks,
 Pavel.

 P.S. Here is summary of what I tried with transformers so far:

 Let’s say I have following monad transformers:

 newtype MaybeMonadT m a = MMT  (m a)

 newtype OuptutMonadT m o a = OMT (m a, o)

 And I am trying to use following monads:

 type M1 a = MaybeMonadT OutputM a
 type M2 a = OuptutMonadT Maybe String a

 Now, they both won’t quite work in the following example:

 foo a b = do
  output before
  r - (liftM2(+)) a b
  when r == Nothing $ output error
  return r


 In case of M1, as soon as I get Nothing in r, computation will stop 
 and return without any output gathered.

 In case of M2, as soon as I get Nothing in r, computation will stop 
 and return only with output gathered so far. That is 
 output error 
 will never be called.


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


Re: [Haskell-cafe] Re: OO in Haskell

2004-11-29 Thread Keean Schupke
Benjamin Franksen wrote:
Of course, stupid me. Ok, I changed that. Still won't compile. I post 
only the

first of four type errors (they are all about 40 lines long; note that the 
inferred type below is almost longer than the complete test program).
 

You'd probably need this as well:
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}
and:
module SimpleOO where
import CommonMain hiding (HDeleteMany, hDeleteMany, TypeCast,typeCast)
import GhcSyntax
import GhcExperiments
import TypeEqBoolGeneric
import TypeEqGeneric1
import TypeCastGeneric1
import Label4
import Data.Typeable -- needed for showing labels
import Data.IORef
import GHC.IOBase
The source code for this and more examples is downloadable from: 
http://www.cwi.nl/~ralf/OOHaskell, The import list is quite long as this
using the HList library from the paper, which has different definitions
of TypeEq available etc... Overlapping instances are not required for
all definitions of type equality, just the generic ones.

   Keean.


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


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread John Meacham
On Mon, Nov 29, 2004 at 11:57:31AM +0100, Benjamin Franksen wrote:
 Can anyone think of a situation where adding a derived instance to an 
 abstract data type breaks one of its invariants?

Yes, I was thinking of this the other day, 

newtype LessThan5 = LessThen5 Int 

new x | x  5 = LessThen5 x
  | otherwise = error not less than five


if someone were allowed to do a 

derive (Enum LessThan5)


in another module, then they could break the invarient with toEnum 6 for
instance.


For safety, one should only be able to remotely derive if all the
constructors of the type are in scope as well as the type. However, this
is too strong of a constraint for deriving Typeable which does not care
about the constructors. It is not clear
what the correct thing to do is, perhaps have 2 types of derivable
classes, ones which need the constructors and ones which don't? Hmm.. 

I am sort of of the practically motivated opinion that Typable should be
a built-in that everything is automatically an instance of, but I don't
know if that is really the right thing to do or just a convinient hack. 

John

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