Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread Alexander Solla


On Nov 15, 2010, at 9:43 AM, Ling Yang wrote:

Specifically: There are some DSLs that can be largely expressed as  
monads,

that inherently play nicely with expressions on non-monadic values.


This, to me, is a big hint that applicative functors could be useful.   
Every monad is an applicative functor.  Given a monad instance for F,  
you can do:


instance Applicative F where
 pure  = return
 (*) = ap

 $ is an alias of fmap.  * can be interpreted as a kind of  
lifting product operator (Examine the types as you learn it.  The  
notation will become transparent once you get it).  So you write  
expressions like:


data F a = F a  -- We'll assume F is instantiated as a monad
data Foo = Foo Int Int Int

foo :: F Foo
foo = Foo $ monad_action_that_returns_an_int_for_your_first_argument
  * monad_action_that_returns_an_int_for_your_second_argument
  * monad_action_that_etc




Your test

test = liftM2 (+) (coin 0.5) (coin 0.5)

translates to:

test = (+) $ (coin 0.5)
   * (coin 0.5)

You can't really express a test in 5 arguments (I think there's no  
liftM5...) but it's easy with $ and *:


test = Five $ one
* two
* three
* four
* five

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


Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread C. McCann
On Mon, Nov 15, 2010 at 12:43 PM, Ling Yang ly...@cs.stanford.edu wrote:
 Specifically: There are some DSLs that can be largely expressed as monads,
 that inherently play nicely with expressions on non-monadic values.
 We'd like to use the functions that already work on the non-monadic
 values for monadic values without calls to liftM all over the place.

It's worth noting that using liftM is possibly the worst possible way
to do this, aesthetically speaking. To start with, liftM is just fmap
with a gratuitous Monad constraint added on top. Any instance of Monad
can (and should) also be an instance of Functor, and if the instances
aren't buggy, then liftM f = (= return . f) = fmap f.

Additionally, in many cases readability is improved by using ($), an
operator synonym for fmap, found in Control.Applicative, I believe.

 The probability monad is a good example.

[snip]
 I'm interested in shortening the description of 'test', as it is
 really just a 'formal addition' of random variables. One can use liftM
 for that:

 test = liftM2 (+) (coin 0.5) (coin 0.5)

Also on the subject of Control.Applicative, note that independent
probabilities like this don't actually require a monad, merely the
ability to lift currying into the underlying functor, which is what
Applicative provides. The operator ((*) :: f (a - b) - f a - f b)
is convenient for writing such expressions, e.g.:

test = (+) $ coin 0.5 * coin 0.5

Monads are only required for lifting control flow into the functor,
which in this case amounts to conditional probability. You would not,
for example, be able to easily use simple lifted functions to write
roll a 6-sided die, flip a coin as many times as the die shows, then
count how many flips were heads.

 I think a good question as a starting point is whether it's possible
 to do this 'monadic instance transformation' for any typeclass, and
 whether or not we were lucky to have been able to instance Num so
 easily (as Num, Fractional can just be seen as algebras over some base
 type plus a coercion function, making them unusually easy to lift if
 most typeclasses actually don't fit this description).

Part of the reason Num was so easy is that all the functions produce
values whose type is the class parameter. Your Num instance could
almost be completely generic for any ((Applicative f, Num a) = f a),
except that Num demands instances of Eq and Show, neither of which can
be blindly lifted the way the numeric operations can.

I imagine it should be fairly obvious why you can't write a
non-trivial generic instance (Show a) = Show (M a) that would work
for any possible monad M--you'd need a function (show :: M a -
String) which is impossible for abstract types like IO, as well as
function types like the State monad. The same applies to (==), of
course. Trivial instances are always possible, e.g. show _ = [not
showable], but then you don't get sensible behavior when a
non-trivial instance does exist, such  as for Maybe or [].

 Note that if we consider this in a 'monadification' context, where we
 are making some choice for each lifted function, treating it as
 entering, exiting, or computing in the monad, instancing the typeclass
 leads to very few choices for each: the monadic versions of +, -, *
 must be obtained with liftM2,the monadic versions of negate, abs,
 signum must be obtained with liftM, and the monadic version of
 fromInteger must be obtained with return . 

Again, this is pretty much the motivation and purpose of
Control.Applicative. Depending on how you want to look at it, the
underlying concept is either lifting multi-argument functions into the
functor step by step, or lifting tuples into the functor, e.g. (f a, f
b) - f (a, b); the equivalence is recovered using fmap with either
(curry id) or (uncurry id).

Note that things do get more complicated if you have to deal with the
full monadic structure, but since you're lifting functions that have
no knowledge of the functor whatsoever they pretty much have to be
independent of it.

 I suppose I'm basically suggesting that the 'next step' is to somehow
 do this calculation of types on real type values, and use an inductive
 programming tool like Djinn to realize the type signatures. I think
 the general programming technique this is getting at is an orthogonal
 version of LISP style where one goes back and forth between types and
 functions, rather than data and code. I would also appreciate any
 pointers to works in that area.

Well, I don't think there's any good way to do this in Haskell
directly, in general. There's a GHC extension that can automatically
derive Functor for many types, but nothing to automatically derive
Applicative as far as I know (other than in trivial cases with newtype
deriving)--I suspect due to Applicative instances being far less often
uniquely determined than for Functor. And while a fully generic
instance can be written and used for any Applicative and Num, the
impossibility of sensible instances for Show and Eq, 

Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread Ling Yang
See my reply to Alex's post for my perspective on how this relates to
applicative functors, reproduced here:

 This, to me, is a big hint that applicative functors could be useful.

Indeed, the ideas here also apply to applicative functors; it is just the 
lifting primitives that will be different; instead of having liftMN, we can 
use $ and * to lift the functions. We could have done this for Num and 
Maybe (suppose Maybe is an instance of Applicative):

instance (Num a) = Num (Maybe a) where
   (+) = \x y - (+) $ x * y
   (-) = \x y - (-) $ x * y
   (*) = \x y - (+) $ x * y
   abs = abs $
   signum = signum $
   fromInteger = pure . fromInteger

The larger goal remains the same: autolifting in a principled manner.

However, you actually bring up a very good point; what if it is really only 
the applicative functors that this method works on in general, that there is 
no 'use case' for considering this autolifting for monads in particular?
I think the answer lies in the fact that monads can be 'flattened;' that is, 
realizations of the type m (m a) - m a are mechanical (in the form of 'join') 
given that = is defined. This is important when we have a typeclass that 
also has monadic signatures. To be more concrete, consider how this function 
could be used in a 'monadic DSL':

enter x = case x of
   0 - Nothing
   _ - Just hi

The type of 'enter' is one case of the general from 'a - M b'. If we were 
instancing a typeclass that had an 'a - M b' function, we'd need a function 
of type 'M a - M b'. This would be accomplished by

enter' = join . liftM enter

So the set of lifting primitives must include at least some way to get M a - 
M b from 'a - M b'---which requires that M is a monad, not just an 
applicative functor.

Thanks for the mention of applicative functors; I should have included them in 
the original post.

Lingfeng Yang
lyang at cs dot stanford dot edu


I should have included a mention of Applicative in my original post.

 Part of the reason Num was so easy is that all the functions produce
 values whose type is the class parameter. Your Num instance could
 almost be completely generic for any ((Applicative f, Num a) = f a),
 except that Num demands instances of Eq and Show, neither of which can
 be blindly lifted the way the numeric operations can.

 I imagine it should be fairly obvious why you can't write a
 non-trivial generic instance (Show a) = Show (M a) that would work
 for any possible monad M--you'd need a function (show :: M a -
 String) which is impossible for abstract types like IO, as well as
 function types like the State monad. The same applies to (==), of
 course. Trivial instances are always possible, e.g. show _ = [not
 showable], but then you don't get sensible behavior when a
 non-trivial instance does exist, such  as for Maybe or [].

Good point. This is where we can start defining restrictions for when
this automatic lifting can or cannot take place. I reference the
concept of 'runnable monads' here, from

[Erwig and Ren 2004] Monadification of Functional Programs

A 'runnable monad' is a monad with an exit function:

class (Monad m) = Runnable m where
exit : m a - a

And yes, for monads like IO, no one would really have a need for
'exit' outside of the cases where they need unsafePerformIO. However,
for Maybe and Prob, 'exit' is extremely useful. In fact, in the
probability monad, if you could not exit the monad, you could not get
anything done, as the real use is around sampling and computing
probabilities, which are of non-monadic types.

Provided M is a runnable monad,

class (Show a) = Show (M a) where
show = show . exit

I'm aware of the limitations of this approach; I just want to come up
with a set of primitives that characterize the cases where
autolifting/monadic instancing is useful.


On Mon, Nov 15, 2010 at 11:19 AM, C. McCann c...@uptoisomorphism.net wrote:
 On Mon, Nov 15, 2010 at 12:43 PM, Ling Yang ly...@cs.stanford.edu wrote:
 Specifically: There are some DSLs that can be largely expressed as monads,
 that inherently play nicely with expressions on non-monadic values.
 We'd like to use the functions that already work on the non-monadic
 values for monadic values without calls to liftM all over the place.

 It's worth noting that using liftM is possibly the worst possible way
 to do this, aesthetically speaking. To start with, liftM is just fmap
 with a gratuitous Monad constraint added on top. Any instance of Monad
 can (and should) also be an instance of Functor, and if the instances
 aren't buggy, then liftM f = (= return . f) = fmap f.

 Additionally, in many cases readability is improved by using ($), an
 operator synonym for fmap, found in Control.Applicative, I believe.

 The probability monad is a good example.

 [snip]
 I'm interested in shortening the description of 'test', as it is
 really just a 'formal addition' of random variables. One can use liftM
 for that:

 test = liftM2 (+) (coin 0.5) 

Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread Bas van Dijk
On Mon, Nov 15, 2010 at 6:43 PM, Ling Yang ly...@cs.stanford.edu wrote:
 ...
 One alternate way of doing this, however, is instancing the
 typeclasses of the ordinary values with their monadic versions:

 instance (Num a) = Num (Prob a) where
        (+) = liftM2 (+)
        (*) = liftM2 (*)
        abs = liftM abs
        signum = liftM signum
        fromInteger = return . fromInteger

 instance (Fractional a) = Fractional (Prob a) where
        fromRational = return . fromRational
        (/) = liftM2 (/)

You may also like to look at Conal Elliott's applicative-numbers package:

http://hackage.haskell.org/package/applicative-numbers

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


Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread Alberto G. Corona
I like your autolifting stuff, and the runnable concept.


 2010/11/15 Ling Yang ly...@cs.stanford.edu

 See my reply to Alex's post for my perspective on how this relates to
 applicative functors, reproduced here:

  This, to me, is a big hint that applicative functors could be useful.
 
 Indeed, the ideas here also apply to applicative functors; it is just the
 lifting primitives that will be different; instead of having liftMN, we
 can use $ and * to lift the functions. We could have done this for Num
 and Maybe (suppose Maybe is an instance of Applicative):
 
 instance (Num a) = Num (Maybe a) where
(+) = \x y - (+) $ x * y
(-) = \x y - (-) $ x * y
(*) = \x y - (+) $ x * y
abs = abs $
signum = signum $
fromInteger = pure . fromInteger
 
 The larger goal remains the same: autolifting in a principled manner.
 
 However, you actually bring up a very good point; what if it is really
 only the applicative functors that this method works on in general, that
 there is no 'use case' for considering this autolifting for monads in
 particular?
 I think the answer lies in the fact that monads can be 'flattened;' that
 is, realizations of the type m (m a) - m a are mechanical (in the form of
 'join') given that = is defined. This is important when we have a
 typeclass that also has monadic signatures. To be more concrete, consider
 how this function could be used in a 'monadic DSL':
 
 enter x = case x of
0 - Nothing
_ - Just hi
 
 The type of 'enter' is one case of the general from 'a - M b'. If we
 were instancing a typeclass that had an 'a - M b' function, we'd need a
 function of type 'M a - M b'. This would be accomplished by
 
 enter' = join . liftM enter
 
 So the set of lifting primitives must include at least some way to get M
 a - M b from 'a - M b'---which requires that M is a monad, not just an
 applicative functor.
 
 Thanks for the mention of applicative functors; I should have included
 them in the original post.
 
 Lingfeng Yang
 lyang at cs dot stanford dot edu
 

 I should have included a mention of Applicative in my original post.

  Part of the reason Num was so easy is that all the functions produce
  values whose type is the class parameter. Your Num instance could
  almost be completely generic for any ((Applicative f, Num a) = f a),
  except that Num demands instances of Eq and Show, neither of which can
  be blindly lifted the way the numeric operations can.

  I imagine it should be fairly obvious why you can't write a
  non-trivial generic instance (Show a) = Show (M a) that would work
  for any possible monad M--you'd need a function (show :: M a -
  String) which is impossible for abstract types like IO, as well as
  function types like the State monad. The same applies to (==), of
  course. Trivial instances are always possible, e.g. show _ = [not
  showable], but then you don't get sensible behavior when a
  non-trivial instance does exist, such  as for Maybe or [].

 Good point. This is where we can start defining restrictions for when
 this automatic lifting can or cannot take place. I reference the
 concept of 'runnable monads' here, from

 [Erwig and Ren 2004] Monadification of Functional Programs

 A 'runnable monad' is a monad with an exit function:

 class (Monad m) = Runnable m where
exit : m a - a

 And yes, for monads like IO, no one would really have a need for
 'exit' outside of the cases where they need unsafePerformIO. However,
 for Maybe and Prob, 'exit' is extremely useful. In fact, in the
 probability monad, if you could not exit the monad, you could not get
 anything done, as the real use is around sampling and computing
 probabilities, which are of non-monadic types.

 Provided M is a runnable monad,

 class (Show a) = Show (M a) where
show = show . exit

 I'm aware of the limitations of this approach; I just want to come up
 with a set of primitives that characterize the cases where
 autolifting/monadic instancing is useful.


 On Mon, Nov 15, 2010 at 11:19 AM, C. McCann c...@uptoisomorphism.net
 wrote:
  On Mon, Nov 15, 2010 at 12:43 PM, Ling Yang ly...@cs.stanford.edu
 wrote:
  Specifically: There are some DSLs that can be largely expressed as
 monads,
  that inherently play nicely with expressions on non-monadic values.
  We'd like to use the functions that already work on the non-monadic
  values for monadic values without calls to liftM all over the place.
 
  It's worth noting that using liftM is possibly the worst possible way
  to do this, aesthetically speaking. To start with, liftM is just fmap
  with a gratuitous Monad constraint added on top. Any instance of Monad
  can (and should) also be an instance of Functor, and if the instances
  aren't buggy, then liftM f = (= return . f) = fmap f.
 
  Additionally, in many cases readability is improved by using ($), an
  operator synonym for fmap, found in Control.Applicative, I believe.
 
  The probability monad is a good example.