Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-22 Thread Henning Thielemann


On Fri, 20 Feb 2009, Louis Wasserman wrote:


Hmmm.  That's probably a better framework to draw on for the general array 
interface.


For a list of all such low-level arrays, see:
  http://www.haskell.org/haskellwiki/Storable_Vector

StorableVectors can also be manipulated in ST monad.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-20 Thread Ryan Ingram
Yeah, I totally forgot about arrays.

But if you're interested in pure computations that use arrays for
intermediate results, maybe uvector[1] is what you are looking for
instead?

  -- ryan

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/uvector

On Thu, Feb 19, 2009 at 2:14 PM, Louis Wasserman
wasserman.lo...@gmail.com wrote:
 Ryan, I didn't get your question after the first read, so here's an actual
 answer to it --

 What I want to preserve about ST is the existence of a guaranteed safe
 runST, really.  I tend to do algorithms and data structures development,
 which almost never requires use of IO, or references of any kind -- usually
 STArrays for intermediate computations are what I'm actually interested in,
 and the actual outputs of my code are generally not monadic at all.

 But I see how it would be useful in general.  I'll add it in.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Thu, Feb 19, 2009 at 2:51 PM, Louis Wasserman wasserman.lo...@gmail.com
 wrote:

 Oh, sweet beans.  I hadn't planned to incorporate mutable references -- my
 code uses them highly infrequently -- but I suppose that since mutable
 references are really equivalent to single-threadedness where referential
 transparency is concerned, that could be pulled off -- I would still want a
 StateThread associated type,  but that'd just be RealWorld for IO and STM, I
 guess.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Thu, Feb 19, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 So, why not use this definition?  Is there something special about ST
 you are trying to preserve?

 -- minimal complete definition:
 -- Ref, newRef, and either modifyRef or both readRef and writeRef.
 class Monad m = MonadRef m where
type Ref m :: * - *
newRef :: a - m (Ref m a)
readRef :: Ref m a - m a
writeRef :: Ref m a - a - m ()
modifyRef :: Ref m a - (a - a) - m a -- returns old value

readRef r = modifyRef r id
writeRef r a = modifyRef r (const a)  return ()
modifyRef r f = do
a - readRef r
writeRef r (f a)
return a

 instance MonadRef (ST s) where
type Ref (ST s) = STRef s
newRef = newSTRef
readRef = readSTRef
writeRef = writeSTRef

 instance MonadRef IO where
type Ref IO = IORef
newRef = newIORef
readRef = readIORef
writeRef = writeIORef

 instance MonadRef STM where
type Ref STM = TVar
newRef = newTVar
readRef = readTVar
writeRef = writeTVar

 Then you get to lift all of the above into a monad transformer stack,
 MTL-style:

 instance MonadRef m = MonadRef (StateT s m) where
type Ref (StateT s m) = Ref m
newRef = lift . newRef
readRef = lift . readRef
writeRef r = lift . writeRef r

 and so on, and the mention of the state thread type in your code is
 just gone, hidden inside Ref m.  It's still there in the type of the
 monad; you can't avoid that:

 newtype MyMonad s a = MyMonad { runMyMonad :: StateT Int (ST s) a }
 deriving (Monad, MonadState, MonadRef)

 But code that relies on MonadRef runs just as happily in STM, or IO,
 as it does in ST.

  -- ryan

 2009/2/19 Louis Wasserman wasserman.lo...@gmail.com:
  It does.  In the most recent version, the full class declaration runs
 
  class MonadST m where
  type StateThread m
  liftST :: ST (StateThread m) a - m a
 
  and the StateThread propagates accordingly.
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
  ganesh.sittampa...@credit-suisse.com wrote:
 
  Henning Thielemann wrote:
   On Mon, 16 Feb 2009, Louis Wasserman wrote:
  
   Overnight I had the following thought, which I think could work
   rather well.  The most basic implementation of the idea is as
   follows:
  
   class MonadST s m | m - s where
   liftST :: ST s a - m a
  
   instance MonadST s (ST s) where ...
   instance MonadST s m = MonadST ...
  
   Like MonadIO, isn't it?
 
  I think it should be, except that you need to track 's' somewhere.
 
  Ganesh
 
 
 
  ==
  Please access the attached hyperlink for an important electronic
  communications disclaimer:
 
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
 
 
  ==
 
 
 
  ___
  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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-20 Thread Louis Wasserman
Hmmm.  That's probably a better framework to draw on for the general array
interface.
The real goal, though, was to be able to abstract out the array usage:
specifically: stateful-mtl provided MonadST and then an ArrayT that drew on
the state thread from a MonadST to hold its own STArray (which I should
probably replace with something from uvector, or provide a separate
transformer implementation backed by uvector.  Having a general MonadArray
typeclass lets you provide several different implementations ^^)

Then, I wrapped an ArrayT into a separate transformer, HeapT, which
implemented the MonadQueue abstraction while using an ArrayT on the back
end.  The final code doesn't see the presence of the array at all, it only
has access to the priority queue operations through the HeapT.

Thank y'all for your helpful comments, by the way =D

Louis Wasserman
wasserman.lo...@gmail.com


On Fri, Feb 20, 2009 at 12:28 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 Yeah, I totally forgot about arrays.

 But if you're interested in pure computations that use arrays for
 intermediate results, maybe uvector[1] is what you are looking for
 instead?

  -- ryan

 [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/uvector

 On Thu, Feb 19, 2009 at 2:14 PM, Louis Wasserman
 wasserman.lo...@gmail.com wrote:
  Ryan, I didn't get your question after the first read, so here's an
 actual
  answer to it --
 
  What I want to preserve about ST is the existence of a guaranteed safe
  runST, really.  I tend to do algorithms and data structures development,
  which almost never requires use of IO, or references of any kind --
 usually
  STArrays for intermediate computations are what I'm actually interested
 in,
  and the actual outputs of my code are generally not monadic at all.
 
  But I see how it would be useful in general.  I'll add it in.
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Thu, Feb 19, 2009 at 2:51 PM, Louis Wasserman 
 wasserman.lo...@gmail.com
  wrote:
 
  Oh, sweet beans.  I hadn't planned to incorporate mutable references --
 my
  code uses them highly infrequently -- but I suppose that since mutable
  references are really equivalent to single-threadedness where
 referential
  transparency is concerned, that could be pulled off -- I would still
 want a
  StateThread associated type,  but that'd just be RealWorld for IO and
 STM, I
  guess.
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Thu, Feb 19, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com
 wrote:
 
  So, why not use this definition?  Is there something special about ST
  you are trying to preserve?
 
  -- minimal complete definition:
  -- Ref, newRef, and either modifyRef or both readRef and writeRef.
  class Monad m = MonadRef m where
 type Ref m :: * - *
 newRef :: a - m (Ref m a)
 readRef :: Ref m a - m a
 writeRef :: Ref m a - a - m ()
 modifyRef :: Ref m a - (a - a) - m a -- returns old value
 
 readRef r = modifyRef r id
 writeRef r a = modifyRef r (const a)  return ()
 modifyRef r f = do
 a - readRef r
 writeRef r (f a)
 return a
 
  instance MonadRef (ST s) where
 type Ref (ST s) = STRef s
 newRef = newSTRef
 readRef = readSTRef
 writeRef = writeSTRef
 
  instance MonadRef IO where
 type Ref IO = IORef
 newRef = newIORef
 readRef = readIORef
 writeRef = writeIORef
 
  instance MonadRef STM where
 type Ref STM = TVar
 newRef = newTVar
 readRef = readTVar
 writeRef = writeTVar
 
  Then you get to lift all of the above into a monad transformer stack,
  MTL-style:
 
  instance MonadRef m = MonadRef (StateT s m) where
 type Ref (StateT s m) = Ref m
 newRef = lift . newRef
 readRef = lift . readRef
 writeRef r = lift . writeRef r
 
  and so on, and the mention of the state thread type in your code is
  just gone, hidden inside Ref m.  It's still there in the type of the
  monad; you can't avoid that:
 
  newtype MyMonad s a = MyMonad { runMyMonad :: StateT Int (ST s) a }
  deriving (Monad, MonadState, MonadRef)
 
  But code that relies on MonadRef runs just as happily in STM, or IO,
  as it does in ST.
 
   -- ryan
 
  2009/2/19 Louis Wasserman wasserman.lo...@gmail.com:
   It does.  In the most recent version, the full class declaration runs
  
   class MonadST m where
   type StateThread m
   liftST :: ST (StateThread m) a - m a
  
   and the StateThread propagates accordingly.
  
   Louis Wasserman
   wasserman.lo...@gmail.com
  
  
   On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
   ganesh.sittampa...@credit-suisse.com wrote:
  
   Henning Thielemann wrote:
On Mon, 16 Feb 2009, Louis Wasserman wrote:
   
Overnight I had the following thought, which I think could work
rather well.  The most basic implementation of the idea is as
follows:
   
class MonadST s m | m - s where
liftST :: ST s a - m a
   
instance MonadST s (ST s) where ...
instance MonadST s m = 

RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Sittampalam, Ganesh
Henning Thielemann wrote:
 On Mon, 16 Feb 2009, Louis Wasserman wrote:
 
 Overnight I had the following thought, which I think could work
 rather well.  The most basic implementation of the idea is as
 follows: 
 
 class MonadST s m | m - s where
 liftST :: ST s a - m a
 
 instance MonadST s (ST s) where ...
 instance MonadST s m = MonadST ...
 
 Like MonadIO, isn't it?

I think it should be, except that you need to track 's' somewhere.

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Louis Wasserman
It does.  In the most recent version, the full class declaration runs

class MonadST m where
type StateThread m
liftST :: ST (StateThread m) a - m a

and the StateThread propagates accordingly.

Louis Wasserman
wasserman.lo...@gmail.com


On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

 Henning Thielemann wrote:
  On Mon, 16 Feb 2009, Louis Wasserman wrote:
 
  Overnight I had the following thought, which I think could work
  rather well.  The most basic implementation of the idea is as
  follows:
 
  class MonadST s m | m - s where
  liftST :: ST s a - m a
 
  instance MonadST s (ST s) where ...
  instance MonadST s m = MonadST ...
 
  Like MonadIO, isn't it?

 I think it should be, except that you need to track 's' somewhere.

 Ganesh


 ==
 Please access the attached hyperlink for an important electronic
 communications disclaimer:

 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html

 ==


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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Ryan Ingram
So, why not use this definition?  Is there something special about ST
you are trying to preserve?

-- minimal complete definition:
-- Ref, newRef, and either modifyRef or both readRef and writeRef.
class Monad m = MonadRef m where
type Ref m :: * - *
newRef :: a - m (Ref m a)
readRef :: Ref m a - m a
writeRef :: Ref m a - a - m ()
modifyRef :: Ref m a - (a - a) - m a -- returns old value

readRef r = modifyRef r id
writeRef r a = modifyRef r (const a)  return ()
modifyRef r f = do
a - readRef r
writeRef r (f a)
return a

instance MonadRef (ST s) where
type Ref (ST s) = STRef s
newRef = newSTRef
readRef = readSTRef
writeRef = writeSTRef

instance MonadRef IO where
type Ref IO = IORef
newRef = newIORef
readRef = readIORef
writeRef = writeIORef

instance MonadRef STM where
type Ref STM = TVar
newRef = newTVar
readRef = readTVar
writeRef = writeTVar

Then you get to lift all of the above into a monad transformer stack, MTL-style:

instance MonadRef m = MonadRef (StateT s m) where
type Ref (StateT s m) = Ref m
newRef = lift . newRef
readRef = lift . readRef
writeRef r = lift . writeRef r

and so on, and the mention of the state thread type in your code is
just gone, hidden inside Ref m.  It's still there in the type of the
monad; you can't avoid that:

newtype MyMonad s a = MyMonad { runMyMonad :: StateT Int (ST s) a }
deriving (Monad, MonadState, MonadRef)

But code that relies on MonadRef runs just as happily in STM, or IO,
as it does in ST.

  -- ryan

2009/2/19 Louis Wasserman wasserman.lo...@gmail.com:
 It does.  In the most recent version, the full class declaration runs

 class MonadST m where
 type StateThread m
 liftST :: ST (StateThread m) a - m a

 and the StateThread propagates accordingly.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
 ganesh.sittampa...@credit-suisse.com wrote:

 Henning Thielemann wrote:
  On Mon, 16 Feb 2009, Louis Wasserman wrote:
 
  Overnight I had the following thought, which I think could work
  rather well.  The most basic implementation of the idea is as
  follows:
 
  class MonadST s m | m - s where
  liftST :: ST s a - m a
 
  instance MonadST s (ST s) where ...
  instance MonadST s m = MonadST ...
 
  Like MonadIO, isn't it?

 I think it should be, except that you need to track 's' somewhere.

 Ganesh


 ==
 Please access the attached hyperlink for an important electronic
 communications disclaimer:

 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html

 ==



 ___
 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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Louis Wasserman
Oh, sweet beans.  I hadn't planned to incorporate mutable references -- my
code uses them highly infrequently -- but I suppose that since mutable
references are really equivalent to single-threadedness where referential
transparency is concerned, that could be pulled off -- I would still want a
StateThread associated type,  but that'd just be RealWorld for IO and STM, I
guess.

Louis Wasserman
wasserman.lo...@gmail.com


On Thu, Feb 19, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 So, why not use this definition?  Is there something special about ST
 you are trying to preserve?

 -- minimal complete definition:
 -- Ref, newRef, and either modifyRef or both readRef and writeRef.
 class Monad m = MonadRef m where
type Ref m :: * - *
newRef :: a - m (Ref m a)
readRef :: Ref m a - m a
writeRef :: Ref m a - a - m ()
modifyRef :: Ref m a - (a - a) - m a -- returns old value

readRef r = modifyRef r id
writeRef r a = modifyRef r (const a)  return ()
modifyRef r f = do
a - readRef r
writeRef r (f a)
return a

 instance MonadRef (ST s) where
type Ref (ST s) = STRef s
newRef = newSTRef
readRef = readSTRef
writeRef = writeSTRef

 instance MonadRef IO where
type Ref IO = IORef
newRef = newIORef
readRef = readIORef
writeRef = writeIORef

 instance MonadRef STM where
type Ref STM = TVar
newRef = newTVar
readRef = readTVar
writeRef = writeTVar

 Then you get to lift all of the above into a monad transformer stack,
 MTL-style:

 instance MonadRef m = MonadRef (StateT s m) where
type Ref (StateT s m) = Ref m
newRef = lift . newRef
readRef = lift . readRef
writeRef r = lift . writeRef r

 and so on, and the mention of the state thread type in your code is
 just gone, hidden inside Ref m.  It's still there in the type of the
 monad; you can't avoid that:

 newtype MyMonad s a = MyMonad { runMyMonad :: StateT Int (ST s) a }
 deriving (Monad, MonadState, MonadRef)

 But code that relies on MonadRef runs just as happily in STM, or IO,
 as it does in ST.

  -- ryan

 2009/2/19 Louis Wasserman wasserman.lo...@gmail.com:
  It does.  In the most recent version, the full class declaration runs
 
  class MonadST m where
  type StateThread m
  liftST :: ST (StateThread m) a - m a
 
  and the StateThread propagates accordingly.
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
  ganesh.sittampa...@credit-suisse.com wrote:
 
  Henning Thielemann wrote:
   On Mon, 16 Feb 2009, Louis Wasserman wrote:
  
   Overnight I had the following thought, which I think could work
   rather well.  The most basic implementation of the idea is as
   follows:
  
   class MonadST s m | m - s where
   liftST :: ST s a - m a
  
   instance MonadST s (ST s) where ...
   instance MonadST s m = MonadST ...
  
   Like MonadIO, isn't it?
 
  I think it should be, except that you need to track 's' somewhere.
 
  Ganesh
 
 
 
 ==
  Please access the attached hyperlink for an important electronic
  communications disclaimer:
 
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
 
 
 ==
 
 
 
  ___
  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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Louis Wasserman
Ryan, I didn't get your question after the first read, so here's an actual
answer to it --

What I want to preserve about ST is the existence of a guaranteed safe
runST, really.  I tend to do algorithms and data structures development,
which almost never requires use of IO, or references of any kind -- usually
STArrays for intermediate computations are what I'm actually interested in,
and the actual outputs of my code are generally not monadic at all.

But I see how it would be useful in general.  I'll add it in.

Louis Wasserman
wasserman.lo...@gmail.com


On Thu, Feb 19, 2009 at 2:51 PM, Louis Wasserman
wasserman.lo...@gmail.comwrote:

 Oh, sweet beans.  I hadn't planned to incorporate mutable references -- my
 code uses them highly infrequently -- but I suppose that since mutable
 references are really equivalent to single-threadedness where referential
 transparency is concerned, that could be pulled off -- I would still want a
 StateThread associated type,  but that'd just be RealWorld for IO and STM, I
 guess.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Thu, Feb 19, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 So, why not use this definition?  Is there something special about ST
 you are trying to preserve?

 -- minimal complete definition:
 -- Ref, newRef, and either modifyRef or both readRef and writeRef.
 class Monad m = MonadRef m where
type Ref m :: * - *
newRef :: a - m (Ref m a)
readRef :: Ref m a - m a
writeRef :: Ref m a - a - m ()
modifyRef :: Ref m a - (a - a) - m a -- returns old value

readRef r = modifyRef r id
writeRef r a = modifyRef r (const a)  return ()
modifyRef r f = do
a - readRef r
writeRef r (f a)
return a

 instance MonadRef (ST s) where
type Ref (ST s) = STRef s
newRef = newSTRef
readRef = readSTRef
writeRef = writeSTRef

 instance MonadRef IO where
type Ref IO = IORef
newRef = newIORef
readRef = readIORef
writeRef = writeIORef

 instance MonadRef STM where
type Ref STM = TVar
newRef = newTVar
readRef = readTVar
writeRef = writeTVar

 Then you get to lift all of the above into a monad transformer stack,
 MTL-style:

 instance MonadRef m = MonadRef (StateT s m) where
type Ref (StateT s m) = Ref m
newRef = lift . newRef
readRef = lift . readRef
writeRef r = lift . writeRef r

 and so on, and the mention of the state thread type in your code is
 just gone, hidden inside Ref m.  It's still there in the type of the
 monad; you can't avoid that:

 newtype MyMonad s a = MyMonad { runMyMonad :: StateT Int (ST s) a }
 deriving (Monad, MonadState, MonadRef)

 But code that relies on MonadRef runs just as happily in STM, or IO,
 as it does in ST.

  -- ryan

 2009/2/19 Louis Wasserman wasserman.lo...@gmail.com:
  It does.  In the most recent version, the full class declaration runs
 
  class MonadST m where
  type StateThread m
  liftST :: ST (StateThread m) a - m a
 
  and the StateThread propagates accordingly.
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
  ganesh.sittampa...@credit-suisse.com wrote:
 
  Henning Thielemann wrote:
   On Mon, 16 Feb 2009, Louis Wasserman wrote:
  
   Overnight I had the following thought, which I think could work
   rather well.  The most basic implementation of the idea is as
   follows:
  
   class MonadST s m | m - s where
   liftST :: ST s a - m a
  
   instance MonadST s (ST s) where ...
   instance MonadST s m = MonadST ...
  
   Like MonadIO, isn't it?
 
  I think it should be, except that you need to track 's' somewhere.
 
  Ganesh
 
 
 
 ==
  Please access the attached hyperlink for an important electronic
  communications disclaimer:
 
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
 
 
 ==
 
 
 
  ___
  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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-18 Thread Henning Thielemann


On Mon, 16 Feb 2009, Louis Wasserman wrote:


Overnight I had the following thought, which I think could work rather well.  
The most basic
implementation of the idea is as follows:

class MonadST s m | m - s where
liftST :: ST s a - m a

instance MonadST s (ST s) where ...
instance MonadST s m = MonadST ...


Like MonadIO, isn't it?___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-18 Thread Henning Thielemann


On Mon, 16 Feb 2009, Louis Wasserman wrote:


I just posted stateful-mtl and pqueue-mtl 1.0.2, making use of the new approach 
to
single-threaded ST wrapping.  I discovered while making the modifications to 
both packages that
the MonadSTTrans type class was unnecessary, enabling a cleaner integration 
with mtl proper.  I'm
pretty confident that this approach is airtight, but let me know if you 
encounter contradictions
or problems.


Btw. there is now also the transformers package. It's Haskell 98, 
however this is certainly not an issue for you, since higher-rank-types as 
in runST are not Haskell 98 anyway.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-18 Thread Louis Wasserman
Yes, it really is like MonadIO -- just capable of being used to produce
guaranteed purely functional results ^^
Louis Wasserman
wasserman.lo...@gmail.com


On Wed, Feb 18, 2009 at 5:43 PM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Mon, 16 Feb 2009, Louis Wasserman wrote:

  I just posted stateful-mtl and pqueue-mtl 1.0.2, making use of the new
 approach to
 single-threaded ST wrapping.  I discovered while making the modifications
 to both packages that
 the MonadSTTrans type class was unnecessary, enabling a cleaner
 integration with mtl proper.  I'm
 pretty confident that this approach is airtight, but let me know if you
 encounter contradictions
 or problems.


 Btw. there is now also the transformers package. It's Haskell 98, however
 this is certainly not an issue for you, since higher-rank-types as in runST
 are not Haskell 98 anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Sittampalam, Ganesh
Well, I think a type system like Clean's that had linear/uniqueness
types could fix the issue by actually checking that the state is
single-threaded (and thus stop you from applying it to a forking
monad). But there's a fundamental operational problem that ST makes
destructive updates, so to support it as a monad transformer in general
you'd need a type system that actually introduced fork operations (which
linear implicit parameters used to do in GHC , but they were removed
because they were quite complicated semantically and noone really used
them).



From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Louis Wasserman
Sent: 16 February 2009 03:31
To: Dan Doel
Cc: Henning Thielemann; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl


Okay, I tested it out and the arrow transformer has the same problem.  I
realized this after I sent the last message -- the point is that at any
particular point, intuitively there should be exactly one copy of a
State# s for each state thread, and it should never get duplicated;
allowing other monads or arrows to hold a State# s in any form allows
them to hold more than one, violating that goal.

I'm not entirely convinced yet that there isn't some really gorgeous
type system magic to fix this issue, like the type-system magic that
motivates the type of runST in the first place, but that's not an
argument that such magic exists...it's certainly an interesting topic to
mull.

Louis Wasserman
wasserman.lo...@gmail.com



On Sun, Feb 15, 2009 at 9:20 PM, Dan Doel dan.d...@gmail.com wrote:


On Sunday 15 February 2009 9:44:42 pm Louis Wasserman wrote:
 Hello all,

 I just uploaded stateful-mtl and pqueue-mtl 1.0.1.  The ST
monad
 transformer and array transformer have been removed -- I've
convinced
 myself that a heap transformer backed by an ST array cannot be
 referentially transparent -- and the heap monad is now
available only as a
 basic monad and not a transformer, though it still provides
priority queue
 functionality to any of the mtl wrappers around it.
stateful-mtl retains a
 MonadST typeclass which is implemented by ST and monad
transformers around
 it, allowing computations in the the ST-bound heap monad to
perform ST
 operations in its thread.

 Since this discussion had largely led to the conclusion that
ST can only be
 used as a bottom-level monad, it would be pretty uncool if ST
computations
 couldn't be performed in a monad using ST internally because
the ST thread
 was hidden and there was no way to place ST computations
'under' the outer
 monad.  Anyway, it's essentially just like the MonadIO
typeclass, except
 with a functional dependency on the state type.

 There was a question I asked that never got answered, and I'm
still
 curious: would an ST *arrow* transformer be valid?  Arrows
impose
 sequencing on their operations that monads don't...  I'm going
to test out
 some ideas, I think.


Your proposed type:

 State (Kleisli []) x y = (s, x) - [(s, y)]

is (roughly) isomorphic to:

 x - StateT s [] y = x - s - [(s, y)]

The problem with an ST transformer is that the state parameter
needs to be
used linearly, because that's the only condition under which the
optimization
of mutable update is safe. ST ensures this by construction, as
opposed to
other languages (Clean) that have type systems that can express
this kind of
constraint directly. However, with STT, whether the state
parameter is used
linearly is a function of the wrapped monad. You'd have to give
a more fleshed
out version of your proposed state arrow transformer, but off
the top of my
head, I'm not sure it'd be any better.

-- Dan




==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Josef Svenningsson
On Mon, Feb 16, 2009 at 2:30 AM, wren ng thornton w...@freegeek.org wrote:
 Louis Wasserman wrote:

 I follow.  The primary issue, I'm sort of wildly inferring, is that use of
 STT -- despite being pretty much a State monad on the inside -- allows
 access to things like mutable references?

 That's exactly the problem. The essential reason for ST's existence are
 STRefs which allow mutability.

I'd like to point out one other thing that ST provides, which is often
forgotten. It provides *polymorphic* references. That is, we can
create new references of any type.

So ST is a really magical beast. Not only does it provide mutation, it
also provides mutable references. And these are two different
features. Now, everyone agrees that mutation is not something that you
can implement in a functional language, so ST cannot be implemented in
Haskell for that reason. It has to be given as a primitive. But what
about polymorphic references? Can they be implemented in Haskell? The
Claessen conjecture (after Koen Claessen) is that they cannot be
implemented in Haskell. See the following email for more details:
http://www.haskell.org/pipermail/haskell/2001-September/007922.html

One could try and separate mutation and polymorphic references and
give them as two different primitives and implement ST on top of that.
But I haven't seen anyone actually trying that (or needing it for that
matter).

Cheers,

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread minh thu
2009/2/16 Josef Svenningsson josef.svennings...@gmail.com:
 On Mon, Feb 16, 2009 at 2:30 AM, wren ng thornton w...@freegeek.org wrote:
 Louis Wasserman wrote:

 I follow.  The primary issue, I'm sort of wildly inferring, is that use of
 STT -- despite being pretty much a State monad on the inside -- allows
 access to things like mutable references?

 That's exactly the problem. The essential reason for ST's existence are
 STRefs which allow mutability.

 I'd like to point out one other thing that ST provides, which is often
 forgotten. It provides *polymorphic* references. That is, we can
 create new references of any type.

 So ST is a really magical beast. Not only does it provide mutation, it
 also provides mutable references. And these are two different
 features. Now, everyone agrees that mutation is not something that you
 can implement in a functional language, so ST cannot be implemented in
 Haskell for that reason. It has to be given as a primitive. But what
 about polymorphic references? Can they be implemented in Haskell? The
 Claessen conjecture (after Koen Claessen) is that they cannot be
 implemented in Haskell. See the following email for more details:
 http://www.haskell.org/pipermail/haskell/2001-September/007922.html

 One could try and separate mutation and polymorphic references and
 give them as two different primitives and implement ST on top of that.
 But I haven't seen anyone actually trying that (or needing it for that
 matter).

Actually, I was interested in making a state holding polymorphic
references in the state monad, so that the state could be passed
around. I made an attempt, and if my memory serves me right, it worked
like this : It was based on Dynamics, with an IntMap indexed,
indirectly, by TypeRep, yielding, for each type, a new IntMap,
providing references for any value of that type.

In fact, I think the next stpe would be to have some TH to generate
specific state monads to hold references on specific types.

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Louis Wasserman
Overnight I had the following thought, which I think could work rather
well.  The most basic implementation of the idea is as follows:

class MonadST s m | m - s where
liftST :: ST s a - m a

instance MonadST s (ST s) where ...
instance MonadST s m = MonadST ...

newtype FooT m e = FooT (StateT Foo m e)

instance (Monad m, MonadST s m) = Monad (FooT m) where ...

instance (Monad m, MonadST s m) = MonadBar (FooT m) where
operations using an ST state

instance (Monad m, MonadST s m)  = MonadST s (FooT m) where ...

The point here is that a MonadST instance guarantees that the bottom monad
is an ST -- and therefore single-threaded of necessity -- and grants any
ST-based monad transformers on top of it access to its single state thread.

The more fully general approach to guaranteeing an underlying monad is
single-threaded would be to create a dummy state parameter version of each
single-threaded monad -- State, Writer, and Reader -- and add a typeclass
called MonadThreaded or something.

The real question with this approach would be how to go about unwrapping
ST-based monad transformers in this fashion: I'm thinking that you would
essentially perform unwrapping of the outer monad using an ST computation
which gets lifted to the next-higher monad.  So, say, for example:

newtype MonadST s m = ArrayT e m a = ArrayT {execArrayT :: StateT (STArray
s Int e) m a}

runArrayT :: (Monad m, MonadST s m) = Int - ArrayT e m a - m a
runArrayT n m = liftST (newArray_ (0, n-1)) = evalStateT (execArrayT m)

Key points:
- A MonadST s m instance should *always* imply that the bottom-level monad
is of type ST s, preferably a bottom level provided when defining a monad by
stacking transformers.  The fact that the bottom monad is in ST should
guarantee single-threaded, referentially transparent behavior.
- A non-transformer implementation of an ST-bound monad transformer would
simply involve setting the bottom monad to ST, rather than Identity as for
most monad transformers.
- Unwrapping an ST-bound monad transformer involves no universal
quantification on the state type.  After all transformers have been
unwrapped, it should be possible to invoke runST on the final ST s a.
- Both normal transformers and ST-bound transformers should propagate
MonadST.

I'm going to go try implementing this idea in stateful-mtl now...

Louis Wasserman
wasserman.lo...@gmail.com


On Mon, Feb 16, 2009 at 3:07 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

  Well, I think a type system like Clean's that had linear/uniqueness types
 could fix the issue by actually checking that the state is single-threaded
 (and thus stop you from applying it to a forking monad). But there's a
 fundamental operational problem that ST makes destructive updates, so to
 support it as a monad transformer in general you'd need a type system that
 actually introduced fork operations (which linear implicit parameters used
 to do in GHC , but they were removed because they were quite complicated
 semantically and noone really used them).

  --
 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Louis Wasserman
 *Sent:* 16 February 2009 03:31
 *To:* Dan Doel
 *Cc:* Henning Thielemann; haskell-cafe@haskell.org
 *Subject:* Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

 Okay, I tested it out and the arrow transformer has the same problem.  I
 realized this after I sent the last message -- the point is that at any
 particular point, intuitively there should be exactly one copy of a State# s
 for each state thread, and it should never get duplicated; allowing other
 monads or arrows to hold a State# s in any form allows them to hold more
 than one, violating that goal.

 I'm not entirely convinced yet that there *isn't* some really gorgeous
 type system magic to fix this issue, like the type-system magic that
 motivates the type of runST in the first place, but that's not an argument
 that such magic exists...it's certainly an interesting topic to mull.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Sun, Feb 15, 2009 at 9:20 PM, Dan Doel dan.d...@gmail.com wrote:

 On Sunday 15 February 2009 9:44:42 pm Louis Wasserman wrote:
  Hello all,
 
  I just uploaded stateful-mtl and pqueue-mtl 1.0.1.  The ST monad
  transformer and array transformer have been removed -- I've convinced
  myself that a heap transformer backed by an ST array cannot be
  referentially transparent -- and the heap monad is now available only as
 a
  basic monad and not a transformer, though it still provides priority
 queue
  functionality to any of the mtl wrappers around it.  stateful-mtl
 retains a
  MonadST typeclass which is implemented by ST and monad transformers
 around
  it, allowing computations in the the ST-bound heap monad to perform ST
  operations in its thread.
 
  Since this discussion had largely led to the conclusion that ST can only
 be
  used as a bottom-level monad, it would

RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Sittampalam, Ganesh
I don't think this can be right, because the m - s dependency will
contradict the universal quantification of s required by runST. In other
words, unwrapping the transformers will leave you with an ST computation
for a specific s, which runST will reject.



From: Louis Wasserman [mailto:wasserman.lo...@gmail.com] 
Sent: 16 February 2009 16:01
To: Sittampalam, Ganesh
Cc: Dan Doel; Henning Thielemann; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl


Overnight I had the following thought, which I think could work rather
well.  The most basic implementation of the idea is as follows:

class MonadST s m | m - s where

liftST :: ST s a - m a


instance MonadST s (ST s) where ...
instance MonadST s m = MonadST ...

newtype FooT m e = FooT (StateT Foo m e)

instance (Monad m, MonadST s m) = Monad (FooT m) where ...

instance (Monad m, MonadST s m) = MonadBar (FooT m) where

operations using an ST state


instance (Monad m, MonadST s m)  = MonadST s (FooT m) where ...

The point here is that a MonadST instance guarantees that the bottom
monad is an ST -- and therefore single-threaded of necessity -- and
grants any ST-based monad transformers on top of it access to its single
state thread.

The more fully general approach to guaranteeing an underlying monad is
single-threaded would be to create a dummy state parameter version of
each single-threaded monad -- State, Writer, and Reader -- and add a
typeclass called MonadThreaded or something.

The real question with this approach would be how to go about unwrapping
ST-based monad transformers in this fashion: I'm thinking that you would
essentially perform unwrapping of the outer monad using an ST
computation which gets lifted to the next-higher monad.  So, say, for
example:

newtype MonadST s m = ArrayT e m a = ArrayT {execArrayT :: StateT
(STArray s Int e) m a}

runArrayT :: (Monad m, MonadST s m) = Int - ArrayT e m a - m a
runArrayT n m = liftST (newArray_ (0, n-1)) = evalStateT (execArrayT
m)

Key points: 
- A MonadST s m instance should always imply that the bottom-level monad
is of type ST s, preferably a bottom level provided when defining a
monad by stacking transformers.  The fact that the bottom monad is in ST
should guarantee single-threaded, referentially transparent behavior.
- A non-transformer implementation of an ST-bound monad transformer
would simply involve setting the bottom monad to ST, rather than
Identity as for most monad transformers.
- Unwrapping an ST-bound monad transformer involves no universal
quantification on the state type.  After all transformers have been
unwrapped, it should be possible to invoke runST on the final ST s a.
- Both normal transformers and ST-bound transformers should propagate
MonadST.

I'm going to go try implementing this idea in stateful-mtl now...

Louis Wasserman
wasserman.lo...@gmail.com



On Mon, Feb 16, 2009 at 3:07 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:


Well, I think a type system like Clean's that had
linear/uniqueness types could fix the issue by actually checking that
the state is single-threaded (and thus stop you from applying it to a
forking monad). But there's a fundamental operational problem that ST
makes destructive updates, so to support it as a monad transformer in
general you'd need a type system that actually introduced fork
operations (which linear implicit parameters used to do in GHC , but
they were removed because they were quite complicated semantically and
noone really used them).



From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Louis Wasserman
Sent: 16 February 2009 03:31
To: Dan Doel
Cc: Henning Thielemann; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl


Okay, I tested it out and the arrow transformer has the same
problem.  I realized this after I sent the last message -- the point is
that at any particular point, intuitively there should be exactly one
copy of a State# s for each state thread, and it should never get
duplicated; allowing other monads or arrows to hold a State# s in any
form allows them to hold more than one, violating that goal.

I'm not entirely convinced yet that there isn't some really
gorgeous type system magic to fix this issue, like the type-system magic
that motivates the type of runST in the first place, but that's not an
argument that such magic exists...it's certainly an interesting topic to
mull.

Louis Wasserman
wasserman.lo...@gmail.com



On Sun, Feb 15, 2009 at 9:20 PM, Dan Doel dan.d...@gmail.com
wrote:


On Sunday 15 February 2009 9:44:42 pm Louis Wasserman
wrote:
 Hello all,

 I just uploaded stateful-mtl and pqueue

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Louis Wasserman
But the m - s dependency will have been removed by the time runST gets a
hold of it!  It works, I just tested it.

*Control.Monad.Array.ArrayM :t runST (runArrayT 5 Nothing getContents)
runST (runArrayT 5 Nothing getContents) :: [Maybe a]
*Control.Monad.Array.ArrayM runST (runArrayT 5 Nothing getContents)
[Nothing,Nothing,Nothing,Nothing,Nothing]

There is, unfortunately, one last key point needed in this approach: the
transformer cannot implement MonadTrans, which requires that it work for all
monads.  The hack I added is

class MonadSTTrans s t where
stLift :: MonadST s m = m a - t m a

instance MonadTrans t = MonadSTTrans s t where
stLift = lift

which, as a side effect, makes explicit the distinction between normal monad
transformers and ST-wrapped monad transformers.

Louis Wasserman
wasserman.lo...@gmail.com


On Mon, Feb 16, 2009 at 10:04 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

  I don't think this can be right, because the m - s dependency will
 contradict the universal quantification of s required by runST. In other
 words, unwrapping the transformers will leave you with an ST computation for
 a specific s, which runST will reject.

  --
 *From:* Louis Wasserman [mailto:wasserman.lo...@gmail.com]
 *Sent:* 16 February 2009 16:01
 *To:* Sittampalam, Ganesh
 *Cc:* Dan Doel; Henning Thielemann; haskell-cafe@haskell.org

 *Subject:* Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

 Overnight I had the following thought, which I think could work rather
 well.  The most basic implementation of the idea is as follows:

 class MonadST s m | m - s where
 liftST :: ST s a - m a

 instance MonadST s (ST s) where ...
 instance MonadST s m = MonadST ...

 newtype FooT m e = FooT (StateT Foo m e)

 instance (Monad m, MonadST s m) = Monad (FooT m) where ...

 instance (Monad m, MonadST s m) = MonadBar (FooT m) where
 operations using an ST state

 instance (Monad m, MonadST s m)  = MonadST s (FooT m) where ...

 The point here is that a MonadST instance guarantees that the bottom monad
 is an ST -- and therefore single-threaded of necessity -- and grants any
 ST-based monad transformers on top of it access to its single state thread.

 The more fully general approach to guaranteeing an underlying monad is
 single-threaded would be to create a dummy state parameter version of each
 single-threaded monad -- State, Writer, and Reader -- and add a typeclass
 called MonadThreaded or something.

 The real question with this approach would be how to go about unwrapping
 ST-based monad transformers in this fashion: I'm thinking that you would
 essentially perform unwrapping of the outer monad using an ST computation
 which gets lifted to the next-higher monad.  So, say, for example:

 newtype MonadST s m = ArrayT e m a = ArrayT {execArrayT :: StateT (STArray
 s Int e) m a}

 runArrayT :: (Monad m, MonadST s m) = Int - ArrayT e m a - m a
 runArrayT n m = liftST (newArray_ (0, n-1)) = evalStateT (execArrayT m)

 Key points:
 - A MonadST s m instance should *always* imply that the bottom-level monad
 is of type ST s, preferably a bottom level provided when defining a monad by
 stacking transformers.  The fact that the bottom monad is in ST should
 guarantee single-threaded, referentially transparent behavior.
 - A non-transformer implementation of an ST-bound monad transformer would
 simply involve setting the bottom monad to ST, rather than Identity as for
 most monad transformers.
 - Unwrapping an ST-bound monad transformer involves no universal
 quantification on the state type.  After all transformers have been
 unwrapped, it should be possible to invoke runST on the final ST s a.
 - Both normal transformers and ST-bound transformers should propagate
 MonadST.

 I'm going to go try implementing this idea in stateful-mtl now...

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Mon, Feb 16, 2009 at 3:07 AM, Sittampalam, Ganesh 
 ganesh.sittampa...@credit-suisse.com wrote:

  Well, I think a type system like Clean's that had linear/uniqueness
 types could fix the issue by actually checking that the state is
 single-threaded (and thus stop you from applying it to a forking monad).
 But there's a fundamental operational problem that ST makes destructive
 updates, so to support it as a monad transformer in general you'd need a
 type system that actually introduced fork operations (which linear implicit
 parameters used to do in GHC , but they were removed because they were
 quite complicated semantically and noone really used them).

  --
 *From:* haskell-cafe-boun...@haskell.org [mailto:
 haskell-cafe-boun...@haskell.org] *On Behalf Of *Louis Wasserman
 *Sent:* 16 February 2009 03:31
 *To:* Dan Doel
 *Cc:* Henning Thielemann; haskell-cafe@haskell.org
 *Subject:* Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

   Okay, I tested it out and the arrow transformer has the same problem.
 I realized this after I sent

RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Sittampalam, Ganesh
Oh, I see, every derived monad has to have an 's' in its type somewhere.



From: Louis Wasserman [mailto:wasserman.lo...@gmail.com] 
Sent: 16 February 2009 16:17
To: Sittampalam, Ganesh
Cc: Dan Doel; Henning Thielemann; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl


But the m - s dependency will have been removed by the time runST gets
a hold of it!  It works, I just tested it.

*Control.Monad.Array.ArrayM :t runST (runArrayT 5 Nothing getContents)
runST (runArrayT 5 Nothing getContents) :: [Maybe a]
*Control.Monad.Array.ArrayM runST (runArrayT 5 Nothing getContents)
[Nothing,Nothing,Nothing,Nothing,Nothing]

There is, unfortunately, one last key point needed in this approach: the
transformer cannot implement MonadTrans, which requires that it work for
all monads.  The hack I added is

class MonadSTTrans s t where
stLift :: MonadST s m = m a - t m a

instance MonadTrans t = MonadSTTrans s t where
stLift = lift

which, as a side effect, makes explicit the distinction between normal
monad transformers and ST-wrapped monad transformers.

Louis Wasserman
wasserman.lo...@gmail.com



On Mon, Feb 16, 2009 at 10:04 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:


I don't think this can be right, because the m - s dependency
will contradict the universal quantification of s required by runST. In
other words, unwrapping the transformers will leave you with an ST
computation for a specific s, which runST will reject.



From: Louis Wasserman [mailto:wasserman.lo...@gmail.com] 
Sent: 16 February 2009 16:01
To: Sittampalam, Ganesh
Cc: Dan Doel; Henning Thielemann; haskell-cafe@haskell.org 

Subject: Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl


Overnight I had the following thought, which I think could work
rather well.  The most basic implementation of the idea is as follows:

class MonadST s m | m - s where

liftST :: ST s a - m a


instance MonadST s (ST s) where ...
instance MonadST s m = MonadST ...

newtype FooT m e = FooT (StateT Foo m e)

instance (Monad m, MonadST s m) = Monad (FooT m) where ...

instance (Monad m, MonadST s m) = MonadBar (FooT m) where

operations using an ST state


instance (Monad m, MonadST s m)  = MonadST s (FooT m) where ...

The point here is that a MonadST instance guarantees that the
bottom monad is an ST -- and therefore single-threaded of necessity --
and grants any ST-based monad transformers on top of it access to its
single state thread.

The more fully general approach to guaranteeing an underlying
monad is single-threaded would be to create a dummy state parameter
version of each single-threaded monad -- State, Writer, and Reader --
and add a typeclass called MonadThreaded or something.

The real question with this approach would be how to go about
unwrapping ST-based monad transformers in this fashion: I'm thinking
that you would essentially perform unwrapping of the outer monad using
an ST computation which gets lifted to the next-higher monad.  So, say,
for example:

newtype MonadST s m = ArrayT e m a = ArrayT {execArrayT ::
StateT (STArray s Int e) m a}

runArrayT :: (Monad m, MonadST s m) = Int - ArrayT e m a - m
a
runArrayT n m = liftST (newArray_ (0, n-1)) = evalStateT
(execArrayT m)

Key points: 
- A MonadST s m instance should always imply that the
bottom-level monad is of type ST s, preferably a bottom level provided
when defining a monad by stacking transformers.  The fact that the
bottom monad is in ST should guarantee single-threaded, referentially
transparent behavior.
- A non-transformer implementation of an ST-bound monad
transformer would simply involve setting the bottom monad to ST, rather
than Identity as for most monad transformers.
- Unwrapping an ST-bound monad transformer involves no universal
quantification on the state type.  After all transformers have been
unwrapped, it should be possible to invoke runST on the final ST s a.
- Both normal transformers and ST-bound transformers should
propagate MonadST.

I'm going to go try implementing this idea in stateful-mtl
now...

Louis Wasserman
wasserman.lo...@gmail.com



On Mon, Feb 16, 2009 at 3:07 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:


Well, I think a type system like Clean's that had
linear/uniqueness types could fix the issue by actually checking that
the state is single-threaded (and thus stop you from applying it to a
forking monad). But there's a fundamental operational problem that ST
makes

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Louis Wasserman
I just posted stateful-mtl and pqueue-mtl 1.0.2, making use of the new
approach to single-threaded ST wrapping.  I discovered while making the
modifications to both packages that the MonadSTTrans type class was
unnecessary, enabling a cleaner integration with mtl proper.  I'm pretty
confident that this approach is airtight, but let me know if you encounter
contradictions or problems.

Louis Wasserman
wasserman.lo...@gmail.com


On Mon, Feb 16, 2009 at 10:21 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:

  Oh, I see, every derived monad has to have an 's' in its type somewhere.

  --
 *From:* Louis Wasserman [mailto:wasserman.lo...@gmail.com]
 *Sent:* 16 February 2009 16:17

 *To:* Sittampalam, Ganesh
 *Cc:* Dan Doel; Henning Thielemann; haskell-cafe@haskell.org
 *Subject:* Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

 But the m - s dependency will have been removed by the time runST gets a
 hold of it!  It works, I just tested it.

 *Control.Monad.Array.ArrayM :t runST (runArrayT 5 Nothing getContents)
 runST (runArrayT 5 Nothing getContents) :: [Maybe a]
 *Control.Monad.Array.ArrayM runST (runArrayT 5 Nothing getContents)
 [Nothing,Nothing,Nothing,Nothing,Nothing]

 There is, unfortunately, one last key point needed in this approach: the
 transformer cannot implement MonadTrans, which requires that it work for all
 monads.  The hack I added is

 class MonadSTTrans s t where
 stLift :: MonadST s m = m a - t m a

 instance MonadTrans t = MonadSTTrans s t where
 stLift = lift

 which, as a side effect, makes explicit the distinction between normal
 monad transformers and ST-wrapped monad transformers.

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Mon, Feb 16, 2009 at 10:04 AM, Sittampalam, Ganesh 
 ganesh.sittampa...@credit-suisse.com wrote:

  I don't think this can be right, because the m - s dependency will
 contradict the universal quantification of s required by runST. In other
 words, unwrapping the transformers will leave you with an ST computation for
 a specific s, which runST will reject.

  --
 *From:* Louis Wasserman [mailto:wasserman.lo...@gmail.com]
 *Sent:* 16 February 2009 16:01
 *To:* Sittampalam, Ganesh
 *Cc:* Dan Doel; Henning Thielemann; haskell-cafe@haskell.org

 *Subject:* Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

   Overnight I had the following thought, which I think could work rather
 well.  The most basic implementation of the idea is as follows:

 class MonadST s m | m - s where
 liftST :: ST s a - m a

 instance MonadST s (ST s) where ...
 instance MonadST s m = MonadST ...

 newtype FooT m e = FooT (StateT Foo m e)

 instance (Monad m, MonadST s m) = Monad (FooT m) where ...

 instance (Monad m, MonadST s m) = MonadBar (FooT m) where
 operations using an ST state

 instance (Monad m, MonadST s m)  = MonadST s (FooT m) where ...

 The point here is that a MonadST instance guarantees that the bottom monad
 is an ST -- and therefore single-threaded of necessity -- and grants any
 ST-based monad transformers on top of it access to its single state thread.

 The more fully general approach to guaranteeing an underlying monad is
 single-threaded would be to create a dummy state parameter version of each
 single-threaded monad -- State, Writer, and Reader -- and add a typeclass
 called MonadThreaded or something.

 The real question with this approach would be how to go about unwrapping
 ST-based monad transformers in this fashion: I'm thinking that you would
 essentially perform unwrapping of the outer monad using an ST computation
 which gets lifted to the next-higher monad.  So, say, for example:

 newtype MonadST s m = ArrayT e m a = ArrayT {execArrayT :: StateT
 (STArray s Int e) m a}

 runArrayT :: (Monad m, MonadST s m) = Int - ArrayT e m a - m a
 runArrayT n m = liftST (newArray_ (0, n-1)) = evalStateT (execArrayT m)

 Key points:
 - A MonadST s m instance should *always* imply that the bottom-level
 monad is of type ST s, preferably a bottom level provided when defining a
 monad by stacking transformers.  The fact that the bottom monad is in ST
 should guarantee single-threaded, referentially transparent behavior.
 - A non-transformer implementation of an ST-bound monad transformer would
 simply involve setting the bottom monad to ST, rather than Identity as for
 most monad transformers.
 - Unwrapping an ST-bound monad transformer involves no universal
 quantification on the state type.  After all transformers have been
 unwrapped, it should be possible to invoke runST on the final ST s a.
 - Both normal transformers and ST-bound transformers should propagate
 MonadST.

 I'm going to go try implementing this idea in stateful-mtl now...

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Mon, Feb 16, 2009 at 3:07 AM, Sittampalam, Ganesh 
 ganesh.sittampa...@credit-suisse.com wrote:

  Well, I think a type system like Clean's that had linear/uniqueness
 types could

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Ryan Ingram
Don't use the
 data (context) = type = constructors
syntax, it doesn't do what you want.

All it does is add the context to the constructor B while not
providing it to any of the functions that use it.

A better solution is

 data Bar a = forall b. Foo a b = B a b

or, equivalently, using GADT syntax:

 data Bar a where
B :: Foo a b = a - b - Bar a

Pattern matching on B will bring the Foo a b context into scope which
will fix b via the functional dependency.

However, I prefer this way of solving the problem:

 class Foo a where
type FooVal a
...

 data Bar a = B a (FooVal a)

  -- ryan


2009/2/16 Louis Wasserman wasserman.lo...@gmail.com:
 Is there a way of exploiting functional dependencies in the following
 fashion?

 class Foo a b | a - b where...

 data Foo a b = Bar a = B a b

 This is not ambiguous, because the functional dependency ensures a unique b
 if one exists.  Can this be done without mentioning b as a type variable in
 Bar?

 Louis Wasserman
 wasserman.lo...@gmail.com


 ___
 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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Dan Doel
On Monday 16 February 2009 8:44:21 am Josef Svenningsson wrote:
 On Mon, Feb 16, 2009 at 2:30 AM, wren ng thornton w...@freegeek.org wrote:
  Louis Wasserman wrote:
  I follow.  The primary issue, I'm sort of wildly inferring, is that use
  of STT -- despite being pretty much a State monad on the inside --
  allows access to things like mutable references?
 
  That's exactly the problem. The essential reason for ST's existence are
  STRefs which allow mutability.

 I'd like to point out one other thing that ST provides, which is often
 forgotten. It provides *polymorphic* references. That is, we can
 create new references of any type.

 So ST is a really magical beast. Not only does it provide mutation, it
 also provides mutable references. And these are two different
 features. Now, everyone agrees that mutation is not something that you
 can implement in a functional language, so ST cannot be implemented in
 Haskell for that reason. It has to be given as a primitive. But what
 about polymorphic references? Can they be implemented in Haskell? The
 Claessen conjecture (after Koen Claessen) is that they cannot be
 implemented in Haskell. See the following email for more details:
 http://www.haskell.org/pipermail/haskell/2001-September/007922.html

 One could try and separate mutation and polymorphic references and
 give them as two different primitives and implement ST on top of that.
 But I haven't seen anyone actually trying that (or needing it for that
 matter).

There are a couple approximations you can make for polymorphic references. For 
one, you can encode the types of all the references you've made so far in the 
type of the monad, so you get a type like:

ST r vec1 vec2 a

where vec1 is the types of references coming in, and vec2 is the same going 
out. For instance:

newSTRef :: ST r vec1 (t ::: vec2) (STRef r t)

Or something of that sort. I've fooled with something like this, and it works 
somewhat, but the obvious problem is that how many and what type of references 
you use has to be statically known, which isn't true for ST.

Someone already mentioned using Dynamic as an alternate base (for instance, 
use a Map of dynamics for underlying storage). Of course, the implementation 
of Dynamic in GHC uses unsafeCoerce, just like ST, so you may not count that. 
However, using GADTs, you can implement Dynamic safely for a closed universe 
of types. So you could create a polymorphic reference monad for whatever such 
universe you wished. Further, if you actually had open GADTs, you could 
actually add the relevant type-rep constructor for every type you declared. 
For instance, jhc's implementation of type classes internally uses such a 
GADT, so one could theoretically make a safe Dynamic, and thus a safe 
polymorphic reference monad.

-- Dan

P.S. Here's some code:

{-# LANGUAGE GeneralizedNewtypeDeriving, Rank2Types #-}

module ST where

import Control.Monad.State

import Data.Dynamic
import Data.Maybe

import qualified Data.IntMap as I

newtype ST r a = ST { unST :: State (I.IntMap Dynamic,Int) a } deriving Monad

newtype STRef r t = STR Int

newSTRef :: Typeable t = t - ST r (STRef r t)
newSTRef v = ST $ do (m, i) - get
 put (I.insert i (toDyn v) m, i+1)
 return (STR i)

modifySTRef :: Typeable t = STRef r t - t - ST r ()
modifySTRef (STR j) v = ST $ do (m, i) - get
put (I.insert j (toDyn v) m, i)
return ()

readSTRef :: Typeable t = STRef r t - ST r t
readSTRef (STR j) = ST $ do (m, i) - get
return . fromJust . fromDynamic $ m I.! j

runST :: (forall r. ST r a) - a
runST st = evalState (unST st) (I.empty, 0)

test v f = runST (do r - newSTRef v
 modifySTRef r (f v)
 readSTRef r)

{- test 1 (+1) == 2 -}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Sittampalam, Ganesh
Dan Doel wrote:
 
 Someone already mentioned using Dynamic as an alternate base (for
 instance, use a Map of dynamics for underlying storage). Of course,
 the implementation of Dynamic in GHC uses unsafeCoerce, just like ST,
 so you may not count that.   
 However, using GADTs, you can implement Dynamic safely for a closed
 universe of types. So you could create a polymorphic reference monad
 for whatever such universe you wished. Further, if you actually had
 open GADTs, you could actually add the relevant type-rep constructor
 for every type you declared. For instance, jhc's implementation of
 type classes internally uses such a GADT, so one could theoretically
 make a safe Dynamic, and thus a safe polymorphic reference monad. 

Apart from the other inconveniences, all of these solutions involve
runtime overhead, which is a shame.

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


[Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
Hello all,

I just released two new packages on Hackage, stateful-mtl and pqueue-mtl.

Stateful-mtl provides an ST monad transformer, several useful operations on
generic monad transformers, and a monad transformer intended to cleanly
externally wrap operations on a mutable array (including resizing
operations).  It provides wrappers to generic MArray instances, an array
based on an IntMap, and a specialized transformer that completely wraps what
is essentially a pared-down STArray into a monadic interface that doesn't
mention ST at all.

pqueue-mtl provides implementations of several structures supporting a
generic 'single-in, single-out' paradigm (encapsulated in a typeclass named
Queuelike), including stacks, queues, and several implementations of
priority queues, including primarily a PQueue structure (in
Data.Queue.PQueue) based on a pairing heap.  In addition, the package
provides monad transformers encapsulating single-threaded access to a
Queuelike structure, and provides a fully encapsulated array-backed heap
implementation (using the array transformers from stateful-mtl).

The primary motivation for all this was to improve elegance of graph
algorithms.  The following is an implementation of a shortest-path algorithm
based on the fgl library that returns an IntMap mapping each node to its
parent in a shortest-path tree:

type DijkstraM gr a b = IntMapT (Node, b) (PQueueT (Edge :- b) (State (gr a
b)))

expand :: (Num b, Ord b, MonadQueue (Edge :- b) m) = b - Context a b - m
()
expand d cxt = let x = node' cxt -- node being expanded
in queueInsertAll [(y, x) :- (d + w) | (y, w) - lsuc' cxt]

dijkstraM :: (Graph gr, Num b, Ord b) = DijkstraM gr a b ()
dijkstraM = execMaybeT $ forever $ do  -- this line repeats a monadic
operation until a pattern match fails
False - gets isEmpty
Just ((v, w) :- d) - queueExtract
statefully (match v) =? \ c - writeAt v (w, d)  expand d c --
performs an action if the match does not return Nothing

dijkstra :: (Graph gr, Num b, Ord b) = gr a b - Node - IntMap (Node, b)
dijkstra g v = evalState (runQueueTOn (execIntMapT_ dijkstraM) [(v, v) :-
0]) g

As an imperative programmer for many years, this is pretty much the most
intuitive implementation of Dijkstra's algorithm that I've seen.  Let me
know what you think.

Louis Wasserman
wasserman.lo...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Sittampalam, Ganesh
 Stateful-mtl provides an ST monad transformer, 

Is this safe? e.g. does it work correctly on [], Maybe etc?

If not this should be flagged very prominently in the documentation.

Cheers,

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Reid Barton
On Sun, Feb 15, 2009 at 09:59:28PM -, Sittampalam, Ganesh wrote:
  Stateful-mtl provides an ST monad transformer, 
 
 Is this safe? e.g. does it work correctly on [], Maybe etc?
 
 If not this should be flagged very prominently in the documentation.

It is not safe: it has the same problem as the STMonadTrans package,
discussed recently here:

http://www.haskell.org/pipermail/glasgow-haskell-users/2009-February/016554.html

The following code demonstrates that STT violates referential
transparency:

 import Control.Monad
 import Data.STRef
 import Control.Monad.Trans
 import Control.Monad.ST.Trans

 data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show

 instance Monad Tree where
   return = Leaf
   Leaf a = k = k a
   Branch l r = k = Branch (l = k) (r = k)

 foo :: STT s Tree Integer
 foo = do
   x - liftST $ newSTRef 0
   y - lift (Branch (Leaf 1) (Leaf 2))
   when (odd y) (liftST $ writeSTRef x y)
   liftST $ readSTRef x

 main :: IO ()
 main = do
   print $ runSTT foo
   let Branch _ (Leaf x) = runSTT foo
   print x

outputting:

Branch (Leaf 1) (Leaf 1)
0

Demanding the value in the left Leaf affects the value seen in the
right Leaf.

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
I follow.  The primary issue, I'm sort of wildly inferring, is that use of
STT -- despite being pretty much a State monad on the inside -- allows
access to things like mutable references?

More serious question: The issue of nondeterministic branching and the State
monad is something that's occurred to me previously.  Do I understand
correctly that this would require use of an arrow transformer, rather than a
monad?  For a generic State monad, that would be something like

newtype StateArrow a x y = SA (a (s, x) (s,y))

and then StateArrow (Kleisli []) x y translates into approximately (s, x) -
[(s, y)], as desired?

Louis Wasserman
wasserman.lo...@gmail.com


On Sun, Feb 15, 2009 at 4:06 PM, Reid Barton rwbar...@math.harvard.eduwrote:

 On Sun, Feb 15, 2009 at 09:59:28PM -, Sittampalam, Ganesh wrote:
   Stateful-mtl provides an ST monad transformer,
 
  Is this safe? e.g. does it work correctly on [], Maybe etc?
 
  If not this should be flagged very prominently in the documentation.

 It is not safe: it has the same problem as the STMonadTrans package,
 discussed recently here:


 http://www.haskell.org/pipermail/glasgow-haskell-users/2009-February/016554.html

 The following code demonstrates that STT violates referential
 transparency:

  import Control.Monad
  import Data.STRef
  import Control.Monad.Trans
  import Control.Monad.ST.Trans
 
  data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
 
  instance Monad Tree where
return = Leaf
Leaf a = k = k a
Branch l r = k = Branch (l = k) (r = k)
 
  foo :: STT s Tree Integer
  foo = do
x - liftST $ newSTRef 0
y - lift (Branch (Leaf 1) (Leaf 2))
when (odd y) (liftST $ writeSTRef x y)
liftST $ readSTRef x
 
  main :: IO ()
  main = do
print $ runSTT foo
let Branch _ (Leaf x) = runSTT foo
print x

 outputting:

 Branch (Leaf 1) (Leaf 1)
 0

 Demanding the value in the left Leaf affects the value seen in the
 right Leaf.

 Regards,
 Reid

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Henning Thielemann


On Sun, 15 Feb 2009, Louis Wasserman wrote:


I follow.  The primary issue, I'm sort of wildly inferring, is that use of STT 
-- despite being
pretty much a State monad on the inside -- allows access to things like mutable 
references?


I assume that ST must always be the most inner monad, like IO. Is this a 
problem in an application?___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
Well, it makes me sad, I guess.  pqueue-mtl provides an array-backed heap
monad transformer that is supposed to keep its own ST thread, if only for
the sake of retaining a purely functional interface without any externally
visible forall'd types, which is perfectly fine in most cases, but I'd have
to think about whether or not it'd remain referentially transparent if the
ST thread were only visible to a very tightly encapsulated set of commands
(i.e. priority queue operations).

Louis Wasserman
wasserman.lo...@gmail.com


On Sun, Feb 15, 2009 at 5:33 PM, Henning Thielemann 
lemm...@henning-thielemann.de wrote:


 On Sun, 15 Feb 2009, Louis Wasserman wrote:

  I follow.  The primary issue, I'm sort of wildly inferring, is that use of
 STT -- despite being
 pretty much a State monad on the inside -- allows access to things like
 mutable references?


 I assume that ST must always be the most inner monad, like IO. Is this a
 problem in an application?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Ryan Ingram
You can roll your own pure STT monad, at the cost of performance:

-- Do not export any of these constructors, just the types STT and STTRef.
data W = forall a. W !a
data Heap s = Heap !Int !(IntMap W)
newtype STT s m a = STT (StateT (Heap s) m a) deriving (Monad,
MonadTrans, MonadIO, insert other stuff here, but not MonadState)
newtype STTRef s a = Ref Int

liftState :: (MonadState s m) = (s - (a,s)) - m a
liftState f = do
(a, s') - liftM f get
put s'
return a

newSTTRef :: forall s m a. a - STT s m a
newSTTRef a = STT $ liftState go where
go (Heap sz m) = (Ref sz, Heap (sz+1) (insert sz (W a) m)

readSTTRef :: forall s m a. STTRef s a - STT s m a
readSTTRef (Ref n) = STT $ liftM go get where
go (Heap _ m) = case lookup n m of
Just (~(W a)) - unsafeCoerce a
_ - error impossible: map lookup failed.

writeSTTRef :: forall s m a. STTRef s a - a - STT s m ()
writeSTTRef (Ref n) a = STT $ modify go where
go (Heap sz m) = Heap sz (insert n (W a) m)

-- forall s. here makes unsafeCoerce in readSTTRef safe.  Otherwise
references could escape and break unsafeCoerce.
runSTT :: (forall s. STT s m a) - m a
runSTT (STT m) = evalStateT m (Heap 0 empty)

instance (MonadState s m) = MonadState s (STT st m) where
get = lift get
put = lift . put
modify = lift . modify

Unfortunately, you lose garbage collection on referenced data since
it's all stored in an IntMap.  Is there a way to solve this problem,
perhaps using some form of weak reference?  Ideally you'd like to be
able to find that all references to a particular Ref have been GC'd so
that you can reuse that Ref index.  Otherwise eventually the IntMap
will fill up if you keep allocating references and throwing them away.

   -- ryan

2009/2/15 Louis Wasserman wasserman.lo...@gmail.com:
 Well, it makes me sad, I guess.  pqueue-mtl provides an array-backed heap
 monad transformer that is supposed to keep its own ST thread, if only for
 the sake of retaining a purely functional interface without any externally
 visible forall'd types, which is perfectly fine in most cases, but I'd have
 to think about whether or not it'd remain referentially transparent if the
 ST thread were only visible to a very tightly encapsulated set of commands
 (i.e. priority queue operations).

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Sun, Feb 15, 2009 at 5:33 PM, Henning Thielemann
 lemm...@henning-thielemann.de wrote:

 On Sun, 15 Feb 2009, Louis Wasserman wrote:

 I follow.  The primary issue, I'm sort of wildly inferring, is that use
 of STT -- despite being
 pretty much a State monad on the inside -- allows access to things like
 mutable references?

 I assume that ST must always be the most inner monad, like IO. Is this a
 problem in an application?

 ___
 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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
The module I put together already has everything I'd need to do it in terms
of an IntMap with much less work than that -- the generic MonadArray type
class has implementations both in terms of ST and in terms of an IntMap
already.  Only three changes in the Heap implementation would be needed: two
changes from runArrayT_ 16 to evalIntMapT, and one change of ArrayT to
IntMapT.  (Here ArrayT is backed by an STT transformer.)

newtype HeapT e m a = HeapT {execHeapT :: ArrayT e (StateT Int m) a}
deriving (Monad, MonadReader r, MonadST s, MonadWriter w, MonadFix, MonadIO)

-- | Runs an 'HeapT' transformer starting with an empty heap.
runHeapT :: (Monad m, Ord e) = HeapT e m a - m a
runHeapT m = evalStateT (runArrayT_ 16 (execHeapT m)) 0

But I'm still not entirely convinced that the original STT monad with all
its illegal behavior, hidden from the user, couldn't be used internally by
HeapT without exposing non-referential-transparency -- I'm still thinking on
that problem.  (Perhaps it'd be useful to ask, how would this purely
functional implementation of HeapT behave when used as a drop-in replacement
for the STT-backed HeapT?)

Originally I said that I was inferring that the problem with an ST
transformer was that it allowed access to mutable references.  If that's
true, can a priority queue be used to simulate an STRef?  If so, wouldn't
that imply (rather elegantly, in fact) that an STT-backed heap transformer
would violate referential transparency.  (Would the single-threaded array
transformer backing HeapT fail in that fashion as well?)

Louis Wasserman
wasserman.lo...@gmail.com


On Sun, Feb 15, 2009 at 6:15 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 You can roll your own pure STT monad, at the cost of performance:

 -- Do not export any of these constructors, just the types STT and STTRef.
 data W = forall a. W !a
 data Heap s = Heap !Int !(IntMap W)
 newtype STT s m a = STT (StateT (Heap s) m a) deriving (Monad,
 MonadTrans, MonadIO, insert other stuff here, but not MonadState)
 newtype STTRef s a = Ref Int

 liftState :: (MonadState s m) = (s - (a,s)) - m a
 liftState f = do
(a, s') - liftM f get
put s'
return a

 newSTTRef :: forall s m a. a - STT s m a
 newSTTRef a = STT $ liftState go where
go (Heap sz m) = (Ref sz, Heap (sz+1) (insert sz (W a) m)

 readSTTRef :: forall s m a. STTRef s a - STT s m a
 readSTTRef (Ref n) = STT $ liftM go get where
go (Heap _ m) = case lookup n m of
Just (~(W a)) - unsafeCoerce a
_ - error impossible: map lookup failed.

 writeSTTRef :: forall s m a. STTRef s a - a - STT s m ()
 writeSTTRef (Ref n) a = STT $ modify go where
go (Heap sz m) = Heap sz (insert n (W a) m)

 -- forall s. here makes unsafeCoerce in readSTTRef safe.  Otherwise
 references could escape and break unsafeCoerce.
 runSTT :: (forall s. STT s m a) - m a
 runSTT (STT m) = evalStateT m (Heap 0 empty)

 instance (MonadState s m) = MonadState s (STT st m) where
get = lift get
put = lift . put
modify = lift . modify

 Unfortunately, you lose garbage collection on referenced data since
 it's all stored in an IntMap.  Is there a way to solve this problem,
 perhaps using some form of weak reference?  Ideally you'd like to be
 able to find that all references to a particular Ref have been GC'd so
 that you can reuse that Ref index.  Otherwise eventually the IntMap
 will fill up if you keep allocating references and throwing them away.

   -- ryan

 2009/2/15 Louis Wasserman wasserman.lo...@gmail.com:
  Well, it makes me sad, I guess.  pqueue-mtl provides an array-backed heap
  monad transformer that is supposed to keep its own ST thread, if only for
  the sake of retaining a purely functional interface without any
 externally
  visible forall'd types, which is perfectly fine in most cases, but I'd
 have
  to think about whether or not it'd remain referentially transparent if
 the
  ST thread were only visible to a very tightly encapsulated set of
 commands
  (i.e. priority queue operations).
 
  Louis Wasserman
  wasserman.lo...@gmail.com
 
 
  On Sun, Feb 15, 2009 at 5:33 PM, Henning Thielemann
  lemm...@henning-thielemann.de wrote:
 
  On Sun, 15 Feb 2009, Louis Wasserman wrote:
 
  I follow.  The primary issue, I'm sort of wildly inferring, is that use
  of STT -- despite being
  pretty much a State monad on the inside -- allows access to things like
  mutable references?
 
  I assume that ST must always be the most inner monad, like IO. Is this a
  problem in an application?
 
  ___
  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] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread wren ng thornton

Louis Wasserman wrote:

I follow.  The primary issue, I'm sort of wildly inferring, is that use of
STT -- despite being pretty much a State monad on the inside -- allows
access to things like mutable references?


That's exactly the problem. The essential reason for ST's existence are 
STRefs which allow mutability.


With only a single path of execution[1] the destructive mutability 
can't be observed (i.e. ST is observationally equivalent to State which 
performs non-destructive updates). However once nondeterminism, 
concurrency (not parallelism), or backtracking enter the picture the 
bisimilarity goes away and it's possible to observe the mutations and 
break referential transparency.



[1] An intentionally vague phrase. Abstractly speaking nondeterminism, 
concurrency, and backtracking all amount to existing simultaneously at 
multiple points in the program with each of these points moving at an 
independent rate. Since they're independent it's possible for one 
thread to make a change and then have another move to see it. With 
only a single execution point it's not possible to tell what your 
history is, and so you can't know if it changes out from behind you.




More serious question: The issue of nondeterministic branching and the State
monad is something that's occurred to me previously.  Do I understand
correctly that this would require use of an arrow transformer, rather than a
monad?


Nope. You can just use StateT over list or Logic[2] and everything works 
out. Since the state of State/StateT is a persistent data structure[3] 
it's fine to hold onto copies of it from many points along it's update 
history. With a nondeterminism monad you essentially just hold onto 
copies of the state at each choice point, thus it's available whenever 
you need to backtrack.



[2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logict

[3] Whereas using STRefs or similar would enable creating ephemeral data 
structures more familiar to imperative programmers. By their nature, if 
we wanted to keep copies of these throughout their mutation history, 
then we'd have to clone the data structure so that future mutations 
don't affect the old copy. Or equivalently, use a copy-on-write scheme.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
Hello all,

I just uploaded stateful-mtl and pqueue-mtl 1.0.1.  The ST monad transformer
and array transformer have been removed -- I've convinced myself that a heap
transformer backed by an ST array cannot be referentially transparent -- and
the heap monad is now available only as a basic monad and not a transformer,
though it still provides priority queue functionality to any of the mtl
wrappers around it.  stateful-mtl retains a MonadST typeclass which is
implemented by ST and monad transformers around it, allowing computations in
the the ST-bound heap monad to perform ST operations in its thread.

Since this discussion had largely led to the conclusion that ST can only be
used as a bottom-level monad, it would be pretty uncool if ST computations
couldn't be performed in a monad using ST internally because the ST thread
was hidden and there was no way to place ST computations 'under' the outer
monad.  Anyway, it's essentially just like the MonadIO typeclass, except
with a functional dependency on the state type.

There was a question I asked that never got answered, and I'm still curious:
would an ST *arrow* transformer be valid?  Arrows impose sequencing on their
operations that monads don't...  I'm going to test out some ideas, I think.

Louis Wasserman
wasserman.lo...@gmail.com


On Sun, Feb 15, 2009 at 6:45 PM, Louis Wasserman
wasserman.lo...@gmail.comwrote:

 The module I put together already has everything I'd need to do it in terms
 of an IntMap with much less work than that -- the generic MonadArray type
 class has implementations both in terms of ST and in terms of an IntMap
 already.  Only three changes in the Heap implementation would be needed: two
 changes from runArrayT_ 16 to evalIntMapT, and one change of ArrayT to
 IntMapT.  (Here ArrayT is backed by an STT transformer.)

 newtype HeapT e m a = HeapT {execHeapT :: ArrayT e (StateT Int m) a}
 deriving (Monad, MonadReader r, MonadST s, MonadWriter w, MonadFix, MonadIO)

 -- | Runs an 'HeapT' transformer starting with an empty heap.
 runHeapT :: (Monad m, Ord e) = HeapT e m a - m a
 runHeapT m = evalStateT (runArrayT_ 16 (execHeapT m)) 0

 But I'm still not entirely convinced that the original STT monad with all
 its illegal behavior, hidden from the user, couldn't be used internally by
 HeapT without exposing non-referential-transparency -- I'm still thinking on
 that problem.  (Perhaps it'd be useful to ask, how would this purely
 functional implementation of HeapT behave when used as a drop-in replacement
 for the STT-backed HeapT?)

 Originally I said that I was inferring that the problem with an ST
 transformer was that it allowed access to mutable references.  If that's
 true, can a priority queue be used to simulate an STRef?  If so, wouldn't
 that imply (rather elegantly, in fact) that an STT-backed heap transformer
 would violate referential transparency.  (Would the single-threaded array
 transformer backing HeapT fail in that fashion as well?)

 Louis Wasserman
 wasserman.lo...@gmail.com


 On Sun, Feb 15, 2009 at 6:15 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 You can roll your own pure STT monad, at the cost of performance:

 -- Do not export any of these constructors, just the types STT and STTRef.
 data W = forall a. W !a
 data Heap s = Heap !Int !(IntMap W)
 newtype STT s m a = STT (StateT (Heap s) m a) deriving (Monad,
 MonadTrans, MonadIO, insert other stuff here, but not MonadState)
 newtype STTRef s a = Ref Int

 liftState :: (MonadState s m) = (s - (a,s)) - m a
 liftState f = do
(a, s') - liftM f get
put s'
return a

 newSTTRef :: forall s m a. a - STT s m a
 newSTTRef a = STT $ liftState go where
go (Heap sz m) = (Ref sz, Heap (sz+1) (insert sz (W a) m)

 readSTTRef :: forall s m a. STTRef s a - STT s m a
 readSTTRef (Ref n) = STT $ liftM go get where
go (Heap _ m) = case lookup n m of
Just (~(W a)) - unsafeCoerce a
_ - error impossible: map lookup failed.

 writeSTTRef :: forall s m a. STTRef s a - a - STT s m ()
 writeSTTRef (Ref n) a = STT $ modify go where
go (Heap sz m) = Heap sz (insert n (W a) m)

 -- forall s. here makes unsafeCoerce in readSTTRef safe.  Otherwise
 references could escape and break unsafeCoerce.
 runSTT :: (forall s. STT s m a) - m a
 runSTT (STT m) = evalStateT m (Heap 0 empty)

 instance (MonadState s m) = MonadState s (STT st m) where
get = lift get
put = lift . put
modify = lift . modify

 Unfortunately, you lose garbage collection on referenced data since
 it's all stored in an IntMap.  Is there a way to solve this problem,
 perhaps using some form of weak reference?  Ideally you'd like to be
 able to find that all references to a particular Ref have been GC'd so
 that you can reuse that Ref index.  Otherwise eventually the IntMap
 will fill up if you keep allocating references and throwing them away.

   -- ryan

 2009/2/15 Louis Wasserman wasserman.lo...@gmail.com:
  Well, it makes me sad, I guess.  pqueue-mtl provides an 

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Dan Doel
On Sunday 15 February 2009 9:44:42 pm Louis Wasserman wrote:
 Hello all,

 I just uploaded stateful-mtl and pqueue-mtl 1.0.1.  The ST monad
 transformer and array transformer have been removed -- I've convinced
 myself that a heap transformer backed by an ST array cannot be
 referentially transparent -- and the heap monad is now available only as a
 basic monad and not a transformer, though it still provides priority queue
 functionality to any of the mtl wrappers around it.  stateful-mtl retains a
 MonadST typeclass which is implemented by ST and monad transformers around
 it, allowing computations in the the ST-bound heap monad to perform ST
 operations in its thread.

 Since this discussion had largely led to the conclusion that ST can only be
 used as a bottom-level monad, it would be pretty uncool if ST computations
 couldn't be performed in a monad using ST internally because the ST thread
 was hidden and there was no way to place ST computations 'under' the outer
 monad.  Anyway, it's essentially just like the MonadIO typeclass, except
 with a functional dependency on the state type.

 There was a question I asked that never got answered, and I'm still
 curious: would an ST *arrow* transformer be valid?  Arrows impose
 sequencing on their operations that monads don't...  I'm going to test out
 some ideas, I think.

Your proposed type:

  State (Kleisli []) x y = (s, x) - [(s, y)]

is (roughly) isomorphic to:

  x - StateT s [] y = x - s - [(s, y)]

The problem with an ST transformer is that the state parameter needs to be 
used linearly, because that's the only condition under which the optimization 
of mutable update is safe. ST ensures this by construction, as opposed to 
other languages (Clean) that have type systems that can express this kind of 
constraint directly. However, with STT, whether the state parameter is used 
linearly is a function of the wrapped monad. You'd have to give a more fleshed 
out version of your proposed state arrow transformer, but off the top of my 
head, I'm not sure it'd be any better.

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


Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Louis Wasserman
Okay, I tested it out and the arrow transformer has the same problem.  I
realized this after I sent the last message -- the point is that at any
particular point, intuitively there should be exactly one copy of a State# s
for each state thread, and it should never get duplicated; allowing other
monads or arrows to hold a State# s in any form allows them to hold more
than one, violating that goal.

I'm not entirely convinced yet that there *isn't* some really gorgeous type
system magic to fix this issue, like the type-system magic that motivates
the type of runST in the first place, but that's not an argument that such
magic exists...it's certainly an interesting topic to mull.

Louis Wasserman
wasserman.lo...@gmail.com


On Sun, Feb 15, 2009 at 9:20 PM, Dan Doel dan.d...@gmail.com wrote:

 On Sunday 15 February 2009 9:44:42 pm Louis Wasserman wrote:
  Hello all,
 
  I just uploaded stateful-mtl and pqueue-mtl 1.0.1.  The ST monad
  transformer and array transformer have been removed -- I've convinced
  myself that a heap transformer backed by an ST array cannot be
  referentially transparent -- and the heap monad is now available only as
 a
  basic monad and not a transformer, though it still provides priority
 queue
  functionality to any of the mtl wrappers around it.  stateful-mtl retains
 a
  MonadST typeclass which is implemented by ST and monad transformers
 around
  it, allowing computations in the the ST-bound heap monad to perform ST
  operations in its thread.
 
  Since this discussion had largely led to the conclusion that ST can only
 be
  used as a bottom-level monad, it would be pretty uncool if ST
 computations
  couldn't be performed in a monad using ST internally because the ST
 thread
  was hidden and there was no way to place ST computations 'under' the
 outer
  monad.  Anyway, it's essentially just like the MonadIO typeclass, except
  with a functional dependency on the state type.
 
  There was a question I asked that never got answered, and I'm still
  curious: would an ST *arrow* transformer be valid?  Arrows impose
  sequencing on their operations that monads don't...  I'm going to test
 out
  some ideas, I think.

 Your proposed type:

  State (Kleisli []) x y = (s, x) - [(s, y)]

 is (roughly) isomorphic to:

  x - StateT s [] y = x - s - [(s, y)]

 The problem with an ST transformer is that the state parameter needs to be
 used linearly, because that's the only condition under which the
 optimization
 of mutable update is safe. ST ensures this by construction, as opposed to
 other languages (Clean) that have type systems that can express this kind
 of
 constraint directly. However, with STT, whether the state parameter is used
 linearly is a function of the wrapped monad. You'd have to give a more
 fleshed
 out version of your proposed state arrow transformer, but off the top of my
 head, I'm not sure it'd be any better.

 -- Dan

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