Re: [Haskell-cafe] guards in applicative style

2012-09-17 Thread Ryan Ingram
Not exactly what you asked for, but...

filter (uncurry somePredicate) $ (,) $ list1 * list2

does the job.

Using only applicative operations, it's impossible to affect the 'shape' of
the result--this is the difference in power between applicative and monad.

  -- ryan


On Wed, Sep 12, 2012 at 7:40 AM, felipe zapata tifonza...@gmail.com wrote:

 Hi Haskellers,

 Suppose I have two list and I want to calculate
 the cartesian product between the two of them,
 constrained to a predicate.
 In List comprehension notation is just

 result = [ (x, y) | x - list1, y -list2, somePredicate x y ]

 or in monadic notation

 result = do
  x - list1
  y - list2
  guard (somePredicate x y)
 return $ (x,y)

 Then I was wondering if we can do something similar using an applicative
 style

 result = (,) $ list1 * list2 (somePredicate ???)

 The question is then,
 there is a way for defining a guard in applicative Style?

 Thanks in advance,

 Felipe Zapata.



 ___
 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] guards in applicative style

2012-09-12 Thread Lorenzo Bolla
I'm no expert at all, but I would say no.
guard type is:
guard :: MonadPlus m = Bool - m ()

and MonadPlus is a monad plus (ehm...) mzero and mplus
(http://en.wikibooks.org/wiki/Haskell/MonadPlus).
On the other hand Applicative is less than a monad
(http://www.haskell.org/haskellwiki/Applicative_functor), therefore
guard as is cannot be defined.

But, in your specific example, with lists, you can always use filter:
filter (uncurry somePredicate) ((,) $ list1 * list2 (somePredicate ???))

hth,
L.


On Wed, Sep 12, 2012 at 3:40 PM, felipe zapata tifonza...@gmail.com wrote:

 Hi Haskellers,

 Suppose I have two list and I want to calculate
 the cartesian product between the two of them,
 constrained to a predicate.
 In List comprehension notation is just

 result = [ (x, y) | x - list1, y -list2, somePredicate x y ]

 or in monadic notation

 result = do
  x - list1
  y - list2
  guard (somePredicate x y)
 return $ (x,y)

 Then I was wondering if we can do something similar using an applicative style

 result = (,) $ list1 * list2 (somePredicate ???)

 The question is then,
 there is a way for defining a guard in applicative Style?

 Thanks in advance,

 Felipe Zapata.



 ___
 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] guards in applicative style

2012-09-12 Thread Brent Yorgey
Lorenzo is correct, but actually for the wrong reason. =) The *type*
of guard is a historical accident, and the fact that it requires
MonadPlus doesn't really tell us anything.  Let's take a look at its
implementation:

  guard   :: (MonadPlus m) = Bool - m ()
  guard True  =  return ()
  guard False =  mzero

'return' is not specific to Monad; we could just as well use 'pure'.
'mzero' is a method of 'MonadPlus' but there is no reason we can't use
'empty' from the 'Alternative' class.  So we could define

  guardA :: Alternative f = Bool - f ()
  guardA True  = pure ()
  guardA False = empty

(As another example, consider the function 'sequence :: Monad m = [m
a] - m [a]'.  Actually this function does not need Monad at all, it
only needs Applicative.)

However, guardA is not as useful as guard, and it is not possible to
do the equivalent of the example shown using a list comprehension with
a guard.  The reason is that whereas monadic computations can make use
of intermediate computed values to decide what to do next, Applicative
computations cannot.  So there is no way to generate values for x and
y and then pass them to 'guardA' to do the filtering.  guardA can only
be used to conditionally abort an Applicative computation using
information *external* to the Applicative computation; it cannot
express a condition on the intermediate values computed by the
Applicative computation itself.

-Brent

On Wed, Sep 12, 2012 at 03:52:03PM +0100, Lorenzo Bolla wrote:
 I'm no expert at all, but I would say no.
 guard type is:
 guard :: MonadPlus m = Bool - m ()
 
 and MonadPlus is a monad plus (ehm...) mzero and mplus
 (http://en.wikibooks.org/wiki/Haskell/MonadPlus).
 On the other hand Applicative is less than a monad
 (http://www.haskell.org/haskellwiki/Applicative_functor), therefore
 guard as is cannot be defined.
 
 But, in your specific example, with lists, you can always use filter:
 filter (uncurry somePredicate) ((,) $ list1 * list2 (somePredicate ???))
 
 hth,
 L.
 
 
 On Wed, Sep 12, 2012 at 3:40 PM, felipe zapata tifonza...@gmail.com wrote:
 
  Hi Haskellers,
 
  Suppose I have two list and I want to calculate
  the cartesian product between the two of them,
  constrained to a predicate.
  In List comprehension notation is just
 
  result = [ (x, y) | x - list1, y -list2, somePredicate x y ]
 
  or in monadic notation
 
  result = do
   x - list1
   y - list2
   guard (somePredicate x y)
  return $ (x,y)
 
  Then I was wondering if we can do something similar using an applicative 
  style
 
  result = (,) $ list1 * list2 (somePredicate ???)
 
  The question is then,
  there is a way for defining a guard in applicative Style?
 
  Thanks in advance,
 
  Felipe Zapata.
 
 
 
  ___
  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] guards in applicative style

2012-09-12 Thread Ertugrul Söylemez
Brent Yorgey byor...@seas.upenn.edu wrote:

 However, guardA is not as useful as guard, and it is not possible to
 do the equivalent of the example shown using a list comprehension with
 a guard.  The reason is that whereas monadic computations can make use
 of intermediate computed values to decide what to do next, Applicative
 computations cannot.  So there is no way to generate values for x and
 y and then pass them to 'guardA' to do the filtering.  guardA can only
 be used to conditionally abort an Applicative computation using
 information *external* to the Applicative computation; it cannot
 express a condition on the intermediate values computed by the
 Applicative computation itself.

To continue this story, from most applicative functors you can construct
a category, which is interesting for non-monads.  Let's examine the
SparseStream functor, which is not a monad:

data SparseStream a =
SparseStream {
  headS :: Maybe a,
  tailS :: SparseStream a
}

This is an applicative functor,

instance Applicative SparseStream where
pure x = let str = SparseStream (Just x) str in str

SparseStream f fs * SparseStream x xs =
SparseStream (f * x) (fs * xs)

but with a little extension it becomes a category, the wire category:

newtype Wire a b = Wire (a - (Maybe b, Wire a b))

This is like SparseStream, but for each head/tail pair it wants an
argument.  Given a Category instance you can now actually make use of
guardA without resorting to monadic combinators:

guardA p . myStream

This is conceptually how Netwire's applicative FRP works and how events
are implemented.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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