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.louis@gmail.com


On Fri, Feb 20, 2009 at 12:28 PM, Ryan Ingram <ryani.spam@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.louis@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.louis@gmail.com
>
>
> On Thu, Feb 19, 2009 at 2:51 PM, Louis Wasserman <wasserman.louis@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.louis@gmail.com
>>
>>
>> On Thu, Feb 19, 2009 at 2:40 PM, Ryan Ingram <ryani.spam@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.louis@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.louis@gmail.com
>>> >
>>> >
>>> > On Thu, Feb 19, 2009 at 2:10 AM, Sittampalam, Ganesh
>>> > <ganesh.sittampalam@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
>>> >
>>> >
>>
>
>