[Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

Ryan Ingram ryani.spam at gmail.com
Tue May 19 05:30:52 EDT 2009


On Tue, May 19, 2009 at 12:54 AM, Miguel Mitrofanov
<miguelimo38 at yandex.ru> wrote:
> I've posted it once or twice.
>
> newtype C m r a = C ((a -> m r) -> m r)
>
> It's a monad, regardless of whether m is one or not. If you have something
> like "return" and "bind", but not exactly the same, you can make "casting"
> functions
>
> m a -> C m r a
>
> and backwards.

This isn't great, though.  Consider this (slightly generalized) version:

> newtype CpsM c t a = CpsM { unCpsM :: forall b. c b -> (a -> t b) -> t b }

We can easily make this a monad for any c & t:

> instance Monad (CpsM c t) where
>     return x = CpsM $ \_ k -> k x
>     m >>= f  = CpsM $ \c k -> unCpsM m c $ \x -> unCpsM (f x) c k

Here's a useful one:

> -- reify Ord constraint in a data structure
> data OrdConstraint a where
>     HasOrd :: Ord a => OrdConstraint a
> type M = CpsM OrdConstraint S.Set

along with your "casting" functions:

> liftS :: S.Set a -> M a
> liftS s = CpsM $ \c at HasOrd k -> S.unions $ map k $ S.toList s

> runS :: Ord a => M a -> S.Set a
> runS m = unCpsM m HasOrd S.singleton

Now consider this code:

> inner = do
>    x <- liftS (S.fromList [1..3])
>    y <- liftS (S.fromList [1..3])
>    return (x+y)

> outer = do
>    x <- inner
>    y <- inner
>    return (x+y)

If you evaluate (runS outer), eventually you get to a state like this:

= let f x = inner >>= \y -> return (x+y)
      g x2 = liftS (S.fromList [1..3]) >>= \y2 -> return (x2+y2)
      h = HasOrd
      k = \a2 -> unCpsM (g a2) h $ \a -> unCpsM (f a) h S.singleton
in S.unions $ map k [1,2,3]

which, after all the evaluation, leads to this:

= S.unions
      [S.fromList [4,5,6,7,8,9,10],
       S.fromList [5,6,7,8,9,10,11],
       S.fromList [6,7,8,9,10,11,12]]

We didn't really do any better than if we just stuck everything in a
list and converted to a set at the end!

Compare to the result of the same code using the restricted monad
solution (in this case runS = id, liftS = id):

inner >>= \x -> inner >>= \y -> return (x+y)
= (Set [1,2,3] >>= \x -> Set [1,2,3] >>= \y -> return (x+y))
      >>= \x -> inner >>= \y -> return (x+y)
= (S.unions (map (\x -> Set [1,2,3] >>= \y -> return (x+y)) [1,2,3]))
      >>= \x -> inner >>= \y -> return (x+y)
= S.unions [Set [2,3,4], Set [3,4,5], Set [4,5,6]]
      >>= \x -> inner >>= \y -> return (x+y)
= Set [2,3,4,5,6]
      >>= \x -> inner >>= \y -> return (x+y)

Notice how we've already snipped off a bunch of the computation that
the continuation-based version ran; the left-associated >>= let us
pre-collapse parts of the set down, which we will never do until the
end of the CPS version.  (This is obvious if you notice that in the
CPS version, the only HasOrd getting passed around is for the final
result type; we never call S.unions at any intermediate type!)

Of course, you can manually cache the result yourself by wrapping "inner":

> cacheS = liftS . runS
> inner_cached = cacheS inner

A version of "outer" using this version has the same behavior as the
non-CPS version.  But it sucks to have to insert the equivalent of
"optimize this please" everywhere in your code :)

  -- ryan

>
> Jason Dusek wrote on 19.05.2009 10:23:
>>
>> 2009/05/18 Miguel Mitrofanov <miguelimo38 at yandex.ru>:
>>>
>>> On 19 May 2009, at 09:06, Ryan Ingram wrote:
>>>
>>>> This is a common problem with trying to use do-notation; there are
>>>> some cases where you can't make the object an instance of Monad.  The
>>>> same problem holds for Data.Set; you'd can write
>>>>
>>>> setBind :: Ord b => Set a -> (a -> Set b) -> Set b
>>>> setBind m f = unions (map f $ toList m)
>>>>
>>>> but there is no way to use setBind for a definition of >>=
>>>
>>> You can use a continuation trick.
>>
>>  Trick?
>>
>> --
>> Jason Dusek
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list