Re: Reference types

2002-02-07 Thread Ashley Yakeley

At 2002-02-05 16:54, I wrote:

data Ref m a = MkRef
{
get :: m a,
set :: a - m (),
modify :: (a - a) - m ()
};

Better,

data Ref m a = MkRef
{
get :: m a,
set :: a - m ()
};

modify :: (Monad m) = Ref m a - (a - a) - m ();
modify ref map = (get ref) = ((set ref) . map);


-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-07 Thread Ashley Yakeley

At 2002-02-07 00:52, John Hughes wrote:

Hmm. Yes. But you still haven't addressed dropping references created in the
transformed monad back into the underlying one again. 

Oh that's easy:

liftedNewSTRef :: (LiftedMonad (ST s) m) = a - m (Ref (ST s) a);
 liftedNewSTRef = lift . newSTRef;

And this does seem to
be getting rather complicated and expensive... are you sure it's worth the
candle? 

I suspect any alternative will be at least as complicated. Bear in mind 
you are still going to need a type for your references and also get and 
set functions that work in all your monads.

I'm quite happy to have references depend on a state identifier myself.

For instance...?

-- 
Ashley Yakeley, Seattle WA

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



RE: Reference types

2002-02-07 Thread Simon Peyton-Jones

Wow.  One innocent message...

| Oh no, please don't do this! I use the RefMonad class, but 
| *without* the dependency r - m. Why not? Because I want to 
| manipulate (for example) STRefs in monads built on top of the 
| ST monad via monad transformers. So I use the same reference 
| type with *many different* monads! Your change would make 
| this impossible.

I don't think so.


There were really two parts to my message:

1.  Have a single built-in type (Ref), rather than two (IORef and
STRef).
I don't see how that can be anything other than a Good Thing, can it?
The primitive operations over Refs are still non-overloaded, as before:
newIORef :: a - IO (Ref IO a)
newSTRef :: a - ST s (Ref (ST s) a)
...etc...

2.  Have a RefMonad type class to overload the new, read, write
operations over Refs.   But nothing in my message precludes also
having a RefMonad2 class with two parameters, and whatever 
functional dependencies (or lack of them) that you like

class RefMonad2 r m where
   new :: a - m (r a)
   read :: r a - m a
   write :: r a - a - m ()

instance RefMonad2 (Ref IO) IO where ...
instance RefMonad2 (Ref (ST s)) (ST s) where ...

So then it's only a question of who gets the name RefMonad!
(Incidentally, so far as I know, RefMonad isn't in any of the existing
libraries.)


So I conclude:
(1) is a win
(2) is a question of what we name the new (and undoubtedly
useful) class that I tendentiously called RefMonad

Or am I missing something?

Simon


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



RE: Reference types

2002-02-07 Thread Ashley Yakeley

At 2002-02-07 01:19, Simon Peyton-Jones wrote:

1.  Have a single built-in type (Ref), rather than two (IORef and
STRef).
I don't see how that can be anything other than a Good Thing, can it?

The problem is that your Ref type is primitive, which means users 
wouldn't be able to create their own Refs. I suppose the user could 
create a Ref2 type, but wouldn't it be easier to do this:

data Ref m a = MkRef
{
get :: m a,
set :: a - m ()
};

class RefMonad m where
   newRef :: a - m (Ref m a)

This has the advantage of not changing existing library code, only adding 
to it. It works out the same for the user as your proposal, only more 
general.

The kind of generalisation you are proposing is, in my opinion, best done 
explicitly by Haskell. Primitive functions and types should be as simple, 
concrete and primitive as possible. Let Haskell do the clever 
generalisation stuff.

-- 
Ashley Yakeley, Seattle WA

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



RE: Reference types

2002-02-07 Thread John Hughes

Simon writes:

There were really two parts to my message:

1.  Have a single built-in type (Ref), rather than two (IORef and
STRef).
I don't see how that can be anything other than a Good Thing, can it?
The primitive operations over Refs are still non-overloaded, as before:
newIORef :: a - IO (Ref IO a)
newSTRef :: a - ST s (Ref (ST s) a)
...etc...

2.  Have a RefMonad type class to overload the new, read, write
operations over Refs.   But nothing in my message precludes also
having a RefMonad2 class with two parameters, and whatever 
functional dependencies (or lack of them) that you like

class RefMonad2 r m where
   new :: a - m (r a)
   read :: r a - m a
   write :: r a - a - m ()

instance RefMonad2 (Ref IO) IO where ...
instance RefMonad2 (Ref (ST s)) (ST s) where ...

So then it's only a question of who gets the name RefMonad!
(Incidentally, so far as I know, RefMonad isn't in any of the existing
libraries.)

It's in my libraries, and in other people's, with the same definition. Just
not in any standard ones yet. (Proposal in preparation!)

So I conclude:
(1) is a win
(2) is a question of what we name the new (and undoubtedly
useful) class that I tendentiously called RefMonad

OK, I see your point.

However, note that your RefMonad class can only ever have two instances, since
there is no way to define creation of a reference of any type other than Ref
IO or Ref (ST s). My RefMonad class can usefully have many instances. So if
you ask me, the benefit of defining your class is rather limited.

The goal here is to write generic imperative code, that can work over either
underlying monad, right? In that case, why would you use a class which limits
you to one of the two monads IO or ST, when you can equally well use a class
which works over any monad built on top of one of these? I can't see any
reason to use SimonRefMonad when one can instead use JohnRefMonad. Hence I
suggest that I get the nice name!

The functional dependency m-r is important in practice. You get continual
hassle with ambiguous overloading otherwise.

Given that one wants JohnRefMonad( with the functional dependency) anyway, I
can't really see that (1) is much of a win. It doesn't help define instances
of the class. Maybe in some absolute sense it might be a cleaner design, but I
can't see that it's worth breaking code to make this change. (Any imperative
code with explicit type signatures will of course break if you make this
change).

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



RE: Reference types

2002-02-07 Thread Ashley Yakeley

At 2002-02-07 02:09, I wrote:

The kind of generalisation you are proposing is, in my opinion, best done 
explicitly by Haskell. Primitive functions and types should be as simple, 
concrete and primitive as possible. Let Haskell do the clever 
generalisation stuff.

As a rule, I'm opposed to any generalisation in the standard libraries 
over IO and (ST s) that cannot be made to work for user-defined monads. 
People will use them in their code, and those monads will become 
privileged. I admit I have a stake in this, my JVM-Bridge makes 
extensive use of lifted monads, and so I'd like porting code between 
monads to be as easy as possible. The way forward for this is classes and 
types in the standard libraries that generalise over any monad which has 
the necessary properties.

-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-06 Thread Koen Claessen

John Hughes despaired:

 | Oh no, please don't do this! I use the RefMonad class,
 | but *without* the dependency r - m. Why not? Because
 | I want to manipulate (for example) STRefs in monads
 | built on top of the ST monad via monad transformers.
 | So I use the same reference type with *many different*
 | monads! Your change would make this impossible.

Ashley Yakeley soothingly suggested:

 | I don't think so. [...]
 :
 | data Ref m a = MkRef
 | {
 | get :: m a,
 | set :: a - m (),
 | modify :: (a - a) - m ()
 | };

Hm... this looks nice. With slight name changes this
becomes:

  data Ref m a =
MkRef
  { readRef  :: m a
  , writeRef :: a - m ()
  }

(such that:

  readRef  :: Ref m a - m a
  writeRef :: Ref m a - a - m ()

)

Further, Ashley writes:

 | The point is that the m - r dependency is also
 | unnecessary, except when you want a new standard ref
 | for a monad.

Not really, the m - r is still there in practise, since you
want to be able to use the 'readRef' and 'writeRef'
operators, which work on the monad m, and you want them to
work on the monad (t m).

In this case one can simply lift the reference, like this:

  liftRef :: MonadTrans t = Ref m a - Ref (t m) a
  liftRef ref =
MkRef
  { readRef  = lift (readRef ref)
  , writeRef = \a - lift (writeRef ref a)
  }

Look, ma, no type classes!

/Koen.

--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.

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



Re: Reference types

2002-02-06 Thread Ashley Yakeley

At 2002-02-06 00:33, Koen Claessen wrote:

Hm... this looks nice. With slight name changes this
becomes:

Oh if you must. I decided that Refs were _so_ fundamental that anytime 
you get, set or modify anything it could probably be represented as a 
Ref, so the functions merit highly generic names. And 'read' and 'write' 
are for streams IMO.

Not really, the m - r is still there in practise, since you
want to be able to use the 'readRef' and 'writeRef'
operators, which work on the monad m, and you want them to
work on the monad (t m).

So how is that an m - r dependency? Nothing is stopping the programmer 
have two different kinds of reference for the same monad, and 'readRef' 
and 'writeRef' will work on any Ref.


-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-06 Thread John Hughes


John Hughes despaired:

 | Oh no, please don't do this! I use the RefMonad class,
 | but *without* the dependency r - m. Why not? Because
 | I want to manipulate (for example) STRefs in monads
 | built on top of the ST monad via monad transformers.
 | So I use the same reference type with *many different*
 | monads! Your change would make this impossible.

Ashley Yakeley soothingly suggested:

 | I don't think so. [...]
 :
 | data Ref m a = MkRef
 | {
 | get :: m a,
 | set :: a - m (),
 | modify :: (a - a) - m ()
 | };

Koen commented:

Hm... this looks nice. With slight name changes this
becomes:

  data Ref m a =
MkRef
  { readRef  :: m a
  , writeRef :: a - m ()
  }

No no no! This still makes the reference type depend on the monad type, which
means that I cannot manipulate the same reference in two different monads! One
of the things I want to do sometimes is to, say, add exceptions using a monad
transformer during just *part* of an ST computation. That means I want to
manipulate the *same* references in both the unadorned ST monad and the
transformed one.

Further, Ashley writes:

 | The point is that the m - r dependency is also
 | unnecessary, except when you want a new standard ref
 | for a monad.

No no no! Well, preferably not. I find that removing that dependency creates a
lot of ambiguity in the overloading: if one uses a reference locally, the
type-checker cannot infer (from the type of the monad) what kind of reference
should be used. That forces a lot of explicit type information to be added,
which just clutters programs unnecessarily.

Koen says:

Not really, the m - r is still there in practise, since you
want to be able to use the 'readRef' and 'writeRef'
operators, which work on the monad m, and you want them to
work on the monad (t m).

In this case one can simply lift the reference, like this:

  liftRef :: MonadTrans t = Ref m a - Ref (t m) a
  liftRef ref =
MkRef
  { readRef  = lift (readRef ref)
  , writeRef = \a - lift (writeRef ref a)
  }

Look, ma, no type classes!

No no no! I don't want to have to *transform* references in order to use them
in another monad! Suppose I've built a large structure, such as a UNION-FIND
forest, and then I want to work in an extended monad for a little. Should I
transform the entire structure in order to continue working on it? Afterwards,
when I return to the underlying monad, I would need to coerce the references
back again... I would need

  dropRef :: MonadTrans t = Ref (t m) a - Ref m a

How would you provide that?? This is beginning to sound expensive. And all of
this, just because of an arbitrary type distinction between types which are
actually the same!

I'm using monad transformers heavily now, and often switching between
monads. I find it a very modular and attractive way of programming, and in
this context I'm (still) convinced that making reference types depend on the
monad is a Really Bad Idea!

The most reasonable approach I can see if one were to do this, would be just
to manipulate references in the monad they belong to (normally ST or IO), and
explicitly lift reference operations to the current monad at each use. That
could be awkward, since if one has applied several monad transformers then the
lifting might be in several stages (and don't say overlapping instances). It
also would hinder one from writing generic reference-using code, that would
work in either an unadorned ST or IO monad or a transformed one. In fact, it
seems to lose most of the benefit of overloading the reference operations in
the first place!

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



Re: Reference types

2002-02-06 Thread Ashley Yakeley

At 2002-02-06 01:09, John Hughes wrote:

No no no! This still makes the reference type depend on the monad type, which
means that I cannot manipulate the same reference in two different monads! 

Yes you can. Consider:

-- m somehow uses 'rep' internally
class (Monad rep, Monad m) = LiftedMonad rep m where
{
lift :: rep a - m a;
}

instance LiftedMonad (ST s) (ST s) where
{
lift = id;
}

instance LiftedMonad (ST s) TransformedMonad where
...

liftRef :: (LiftedMonad rep m) = Ref rep a - Ref m a;
liftRef ref = ...

newSTRef :: a - Ref (ST s) a;
 
newSTLiftedRef :: (LiftedMonad (ST s) m) = a - Ref m a;
newSTLiftedRef = liftRef . newSTRef;

With me so far? Now here's the clever bit: Refs created with 
newSTLiftedRef are of type '(LiftedMonad (ST s) m) = Ref m a'. This 
means they will work equally well as 'Ref (ST s) a' as they will as 'Ref 
TransformedMonad a'.

-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-06 Thread Ashley Yakeley

At 2002-02-06 00:54, Koen Claessen wrote:

You are completely right, of course I meant r - m!

Right. There's the equivalent of an r - m dependency because m is a 
parameter in the Ref type constructor. But it doesn't matter, because you 
can create values of this type:

 myIntRef :: (MyMonad m) = Ref m Int

...i.e., references that work with multiple monads.


-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-06 Thread John Hughes

Ashley Yakeley wrote:

At 2002-02-06 01:09, John Hughes wrote:

No no no! This still makes the reference type depend on the monad type, which
means that I cannot manipulate the same reference in two different monads! 

Yes you can. Consider:

-- m somehow uses 'rep' internally
class (Monad rep, Monad m) = LiftedMonad rep m where
{
lift :: rep a - m a;
}

instance LiftedMonad (ST s) (ST s) where
{
lift = id;
}

instance LiftedMonad (ST s) TransformedMonad where
...

liftRef :: (LiftedMonad rep m) = Ref rep a - Ref m a;
liftRef ref = ...

newSTRef :: a - Ref (ST s) a;
 
newSTLiftedRef :: (LiftedMonad (ST s) m) = a - Ref m a;
newSTLiftedRef = liftRef . newSTRef;

With me so far? Now here's the clever bit: Refs created with 
newSTLiftedRef are of type '(LiftedMonad (ST s) m) = Ref m a'. This 
means they will work equally well as 'Ref (ST s) a' as they will as 'Ref 
TransformedMonad a'.

Well, I'm still not convinced. A reference *value* can't have the type

  (LiftedMonad (ST s) m) = Ref m a

This is the type of a function, which given a dictionary returns a reference.
Moreover, since when I write

  do r - newSTLiftedRef x
 ...

then I am effectively lambda-binding r, then r cannot have this type. It can only
have an instance of it ... which ties r to the monad m.

Am I missing something here?  Seems to me, to do what you're suggesting I
would have to put the context inside the Ref type itself:

  data Ref s a = Ref 
 { readRef :: forall m. LiftedMonad (ST s) m = m a,
   writeRef :: forall m. LiftedMonad (ST s) m = a - m () }

But now the s had to go back in the type of the reference...

Are you really in Seattle? If so, you must be a real nightbird or a
tremendously early riser!

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



Re: Reference types

2002-02-06 Thread Ashley Yakeley

At 2002-02-06 03:38, John Hughes wrote:

Well, I'm still not convinced. A reference *value* can't have the type

  (LiftedMonad (ST s) m) = Ref m a

Oh, yeah, you're right. I made a mistake here:

 newSTRef :: a - Ref (ST s) a;
 
newSTLiftedRef :: (LiftedMonad (ST s) m) = a - Ref m a;

This should of course be:

 newSTRef :: a - (ST s) (Ref (ST s) a);
 
newSTLiftedRef :: (LiftedMonad (ST s) m) = a - m (Ref m a);

...which won't help, because the Ref will only work in the monad that 
created it. But I have a solution...

data Ref m a = MkRef
{
get :: m a,
set :: a - m (),
modify :: (a - a) - m ()
};

-- m somehow uses 'rep' internally
class (Monad rep, Monad m) = LiftedMonad rep m where
{
lift :: rep a - m a;
}

instance LiftedMonad (ST s) (ST s) where
{
lift = id;
}

instance LiftedMonad (ST s) TransformedMonad where
...

liftRef :: (LiftedMonad rep m) = Ref rep a - Ref m a;
liftRef ref = ...

newSTRef :: a - (ST s) (Ref (ST s) a);

 getLifted :: (LiftedMonad rep m) = Ref rep a - m a;
 getLifted = get . liftRef;

 setLifted :: (LiftedMonad rep m) = Ref rep a - a - m ();
 setLifted = set . liftRef;

 modifyLifted :: (LiftedMonad rep m) = Ref rep a - (a - a) - m ();
 modifyLifted = modify . liftRef;

Now when you need a new Ref, use newSTRef, and when you need to use the 
Ref, use getLifted, setLifted and modifyLifted. They'll work equally well 
with (ST s) as with TransformedMonad.

Are you really in Seattle? If so, you must be a real nightbird or a
tremendously early riser!

Um, yeah, that's a side effect of unemployment, along with haemorrhaging 
open-source software (see Truth). Does anyone need a Haskell developer in 
the greater Seattle area?

-- 
Ashley Yakeley, Seattle WA

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



RE: Reference types

2002-02-05 Thread Mark P Jones

Hi Simon,

The one parameter scheme that you've described breaks down if you want
to generalize further and allow something like:

  class RefMonad r m where
new   :: a - m (r a)
read  :: r a - m a
write :: r a - a - m ()

  instance RefMonad IORef IO where ...
  instance RefMonad STRef ST where ...
  instance RefMonad Channel IO where ...-- note, this breaks the
  instance RefMonad MVar IO where ...   -- (m - r) dependency

  instance (RefMonad r m, MonadT t) = RefMonad r (t m) where ...
-- and this kills the
-- (r - m) dependency

[This is just an example, not a proposal.]

Note the complete lack of functional dependencies.  I really don't
think they are the right tool here.  Similar uses of fundeps have
appeared in some code for state monads; I don't think they are
appropriate there either.  Bidirectional dependencies are occasionally
useful, but, in general, it is also easy to overuse functional
dependencies (the same, I believe, is true for classes in general).
The simpler type structure you describe looks more appealing to me.

All the best,
Mark

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



Re: Reference types

2002-02-05 Thread C T McBride

Hi Simon

On Tue, 5 Feb 2002, Simon Peyton-Jones wrote:

 2.  I'd be interested to know of any other examples you have of
 *bi-directional* functional depenencies.  The above simplification
 nukes my only convincing example.  (Usually one set of
 type variables determines another, but not vice versa.)

The kind of programming I do at the type level in `Faking It'

  http://www.dur.ac.uk/c.t.mcbride/faking.ps

is fairly ordinary recursive programming on datatype expressions
using type classes with functional dependencies.  Just as many logic
programs have more than one functional (or partial-functional) mode,
so do many type class programs.

An artificial, but simple example

 data Empty

 class Add x y z | x y - z, z x - y

 instance Add Empty y y

 instance Add x y z = Add (Maybe x) y (Maybe z)

The two functional dependencies indicate that the compiler can be expected
either to add or to subtract in order to determine a missing instance
variable.

Of course, depending on the types of the operations for which Add is used,
not all of the possible functional dependencies may be relevant. There
is one example in `Faking It'---zipWith for vectors---which requires two
such dependencies. I'm sure I've got some other examples lurking
about; these things do pop up.

Whether such examples are `convincing' is another matter. Type-level
functional programming is a rather bizarre application of the class
system. I nonetheless find it very useful; I just wish type-level
functional programming was a less bizarre application of something rather
more like functional programming. 

Cheers

Conor

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



Re: Reference types

2002-02-05 Thread Ashley Yakeley

At 2002-02-05 07:50, Simon Peyton-Jones wrote:

   data Ref m a-- References in monad m, values of type a
etc.

You might be interested in:

http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/*checkout*/jvm-bridge/sourc
e/Haskell/Ref.hs?rev=HEADcontent-type=text/plain

data Ref m a = MkRef
{
get :: m a,
set :: a - m (),
modify :: (a - a) - m ()
};

JVM-Bridge uses Refs for fields in Java classes. The monads in question 
are of type (IsJVMMonad m) = m.

As a general rule, if your class has a lot of members of the form a - 
b, where the a's are all the same, it's a clue to consider using a data 
type instead.

-- 
Ashley Yakeley, Seattle WA

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



Re: Reference types

2002-02-05 Thread John Hughes


The basic bind operations etc are overloaded for IO and ST,
but to overload the Ref operations one needs to add 

class RefMonad r m | r - m, m - r where
  newRef   :: a - m (r a)
  readRef  :: r a - m a
  writeRef :: r a - a - m ()

instance RefMonad IORef IO where ...
instance RefMonad (STRef s) (IO s) where ...

A multi-paramter type class is needed.  Notice particularly the
bidirectional functional dependencies.  This is the only convincing
example I know with functional dependencies going both ways.

Or at least it was.  But in a recent conversation with Peter Thiemann
I realised that this is all baloney.  There's a much easier type
structure:

data Ref m a-- References in monad m, values of type a

newIORef :: a - IO (Ref IO a)
readIORef  :: Ref IO a - IO a
writeIORef :: Ref IO a - a - IO ()

newSTRef   :: a - ST s (Ref (ST  s) a)
readSTRef  :: Ref (ST  s) a - ST s a
writeSTRef :: Ref (ST  s) a - a - ST s ()

class RefMonad m where
  newRef   :: a - m (Ref m a)
  readRef  :: Ref m a - m a
  writeRef :: Ref m a - a - m ()

instance RefMonad IO where ...
instance RefMonad (ST s) where ...


No functional dependencies.  No multi-parameter classes.  Pure Haskell
98.  All of this works for mutable arrays too, of course.

Oh no, please don't do this! I use the RefMonad class, but *without* the
dependency r - m. Why not? Because I want to manipulate (for example) STRefs
in monads built on top of the ST monad via monad transformers. So I use the
same reference type with *many different* monads! Your change would make this
impossible.

John

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



Re: Reference types

2002-02-05 Thread Ashley Yakeley

At 2002-02-05 15:10, John Hughes wrote:

Oh no, please don't do this! I use the RefMonad class, but *without* the
dependency r - m. Why not? Because I want to manipulate (for example) STRefs
in monads built on top of the ST monad via monad transformers. So I use the
same reference type with *many different* monads! Your change would make this
impossible.

I don't think so. Provided you have a class that represents your monads, 
I don't see why you can't do this:

class (Monad m) = MyMonad m where
...

myIntRef :: (MyMonad m) = Ref m Int;


...except that with Simon's suggested change you wouldn't be able to 
define your own Refs. I believe the best solution to the problem involves 
leaving the existing functions as is but adding something like this:

data Ref m a = MkRef
{
get :: m a,
set :: a - m (),
modify :: (a - a) - m ()
};

mkRef g s = MkRef g s (\map - do
{
val - g;
s (map val);
});

refBind :: (Monad m) = (m a) - (a - Ref m b) - Ref m b;
refBind ma arb = MkRef
(   ma = (\a - get   (arb a) ))
(\b -  ma = (\a - set   (arb a) b   ))
(\map -ma = (\a - modify(arb a) map ));

class (Monad m) = RefMonad m where
{
newRef   :: a - m (Ref m a);-- standard ref for this monad
};  

instance RefMonad IO where
{
newRef a = do
{
r - newIORef a;
return MkRef (readIORef r) (writeIORef r) (modifyIORef r)
};
};

instance RefMonad (ST s) where
etc.

The point is that the m - r dependency is also unnecessary, except when 
you want a new standard ref for a monad.

-- 
Ashley Yakeley, Seattle WA

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