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

2009-05-19 Thread Miguel Mitrofanov


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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-05-19 Thread Jason Dusek
2009/05/18 Miguel Mitrofanov miguelim...@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-05-19 Thread Taral
On Mon, May 18, 2009 at 10:06 PM, Ryan Ingram ryani.s...@gmail.com wrote:
 On Mon, May 18, 2009 at 3:05 PM, Taral tar...@gmail.com wrote:
 Will this do?

 (=) :: (NFData sa, NFData b) = LI sa - (sa - LI b) - LI b

 No, the problem is that = on monads has no constraints, it must have the 
 type
 LI a - (a - LI b) - LI b

I'm pretty sure you can do something like:

newtype LIMonad x = NFData x = LI x

-- 
Taral tar...@gmail.com
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-05-19 Thread Ryan Ingram
To be fair, you can do this with some extensions; I first saw this in
a paper on Oleg's site [1].  Here's some sample code:

{-# LANGUAGE NoImplicitPrelude, TypeFamilies, MultiParamTypeClasses #-}
module SetMonad where
import qualified Data.Set as S
import qualified Prelude as P (Monad, (=), (), return, fail)
import Prelude hiding (Monad, (=), (), return, fail)

class ConstrainedPoint pa where
type PointElem pa
return :: PointElem pa - pa

class ConstrainedBind ma mb where
type BindElem ma
(=) :: ma - (BindElem ma - mb) - mb
() :: ma - mb - mb
m  n = m = const n

class ConstrainedFail pa where
fail :: String - pa

instance ConstrainedPoint (S.Set a) where
type PointElem (S.Set a) = a
return = S.singleton

instance Ord b = ConstrainedBind (S.Set a) (S.Set b) where
type BindElem (S.Set a) = a
m = f = S.unions $ map f $ S.toList m

test :: S.Set Int
test = do
x - S.fromList [1,2,3]
y - S.fromList [1,2,3]
return (x+y)

-- ghci test
-- fromList [2,3,4,5,6]

  -- ryan

[1] http://www.okmij.org/ftp/Haskell/types.html#restricted-datatypes

On Tue, May 19, 2009 at 12:46 AM, Henning Thielemann
lemm...@henning-thielemann.de wrote:

 On Mon, 18 May 2009, Nicolas Pouillard wrote:

 Excerpts from Jason Dusek's message of Sun May 17 15:45:25 +0200 2009:

  From the documentation:

    LI could be a strict monad and a strict applicative functor.
    However it is not a lazy monad nor a lazy applicative
    functor as required Haskell. Hopefully it is a lazy
    (pointed) functor at least.

 The type I would need for bind is this one:

  (=) :: NFData sa = LI sa - (sa - LI b) - LI b

 And because of the NFData constraint this type bind is less general than
 the
 required one.

 Looks very similar to the operator I need for binding with respect to
 asynchronous exceptions:

 bind :: (Monoid a, Monad m) =
   ExceptionalT e m a - (a - ExceptionalT e m b) - ExceptionalT e m b
 ___
 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] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Miguel Mitrofanov

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.

Jason Dusek wrote on 19.05.2009 10:23:

2009/05/18 Miguel Mitrofanov miguelim...@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@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] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Nicolas Pouillard
Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009:
 To be fair, you can do this with some extensions; I first saw this in
 a paper on Oleg's site [1].  Here's some sample code:

This seems like the same trick as the rmonad package:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rmonad

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


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

2009-05-19 Thread Ryan Ingram
Minor addition, optimize 
(I couldn't help myself!)

  -- ryan

 instance Ord b = ConstrainedBind (S.Set a) (S.Set b) where
type BindElem (S.Set a) = a
m = f = S.unions $ map f $ S.toList m
m  n  = if S.null m then S.empty else n
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-05-19 Thread Sittampalam, Ganesh
Nicolas Pouillard wrote:
 Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009:
 To be fair, you can do this with some extensions; I first saw this in
 a paper on Oleg's site [1].  Here's some sample code:
 
 This seems like the same trick as the rmonad package:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rmonad

It's similar, but rmonad uses an associated datatype to wrap up the
constraint, and doesn't split the Monad class up into separate pieces
(which generally makes type inference harder).

rmonad also supplies an embedding to turn any restricted monad into a
normal monad at the cost of using embed/unEmbed to get into and out of
the embedding.

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] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Ryan Ingram
On Tue, May 19, 2009 at 12:54 AM, Miguel Mitrofanov
miguelim...@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 $ \...@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 miguelim...@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@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

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


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

2009-05-18 Thread Ryan Ingram
On Mon, May 18, 2009 at 3:05 PM, Taral tar...@gmail.com wrote:
 Will this do?

 (=) :: (NFData sa, NFData b) = LI sa - (sa - LI b) - LI b

No, the problem is that = on monads has no constraints, it must have the type
 LI a - (a - LI b) - LI b

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 =

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