On Mon, Nov 15, 2010 at 11:19 AM, C. McCann <
cam@uptoisomorphism.net> wrote:
> On Mon, Nov 15, 2010 at 12:43 PM, Ling Yang <
lyang@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, combined with the
> context-blind nature of Haskell's instance resolution, means that it
> can't be written directly in full generality. It would, however, be
> fairly trivial to manufacture instance declarations for specific types
> using some sort of preprocessor, assuming Show/Eq instances have been
> written manually or by creating trivial ones.
>
> Anyway, you may want to read the paper that introduced Applicative,
> since that seems to describe the subset of generic lifted functions
> you're after:
http://www.soi.city.ac.uk/~ross/papers/Applicative.html
>
> If for some reason you'd rather continue listening to me talk about
> it, I wrote an extended ode to Applicative on Stack Overflow some time
> back that was apparently well-received:
>
http://stackoverflow.com/questions/3242361/haskell-how-is-pronounced/3242853#3242853
>
> - C.
>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe