[Haskell-cafe] Interesting data structure

Ryan Ingram ryani.spam at gmail.com
Thu Dec 27 22:14:41 EST 2007


This monad seems to be basically the same as Prompt; see
http://www.haskell.org/pipermail/haskell-cafe/2007-November/034830.html, the
only difference I see is that Prompt allows the return value's type to
be based on the request instead of forcing everything to be wrapped in a
single result type.

You implemented the monad operations exactly the same as Prompt, and your
bind operator suffers from the same quadratic behavior problem that was
pointed out in that thread.

As was pointed out there, what you are doing is turning the potential side
effects of your computations into a term algebra, which allows you to write
different "interpretation" functions to use when running the calculation
(the reqf passed to runSC).  As far as I can tell, this pattern is general
enough to implement any computation, so it's not surprising that you found
it possible to use it to implement parallel computation.

As an example, here's the State monad implemented in terms of SCalc:

> data StateReq s = Get | Put s
> get :: SCalc (StateReq s) s s
> get = SCStage Get return
> put :: s -> SCalc (StateReq s) s ()
> put s = SCStage (Put s) (const $ return ())
>
> runState :: SCalc (StateReq a) s b -> s -> (a, s)
> runState (SCResult v) s = (v, s)
> runState (SCStage Get cont) s = runState (cont s) s
> runState (SCStage (Put s) cont) _ = runState (cont s) s

I think it's a useful pattern and I definitely am getting a lot of use out
of Prompt in my code.  But I'm trying to figure out the best way
to eliminate the quadratic behavior of (>>=) that is exhibited by, for
example:

foldl1 (>>=) $ take 100 $ repeat $ (\x -> put (x+1) >>= get) $ 0

The only way I've found so far is to wrap Prompt inside of ContT which
solves the problem in much the same way that difference lists (newtype DList
a = [a] -> [a]) solve the problem of quadratic time append for lists.

  -- ryan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071227/fb399eee/attachment.htm


More information about the Haskell-Cafe mailing list