Re: [Haskell-cafe] Do type classes have a partial order?

2011-11-14 Thread Ling Yang
It seems like you would, going by semantics of System F, where types
with type variables name a certain subset of types, = constraints
further restrict the types of the same shape (are they an
independent kind of restriction?),  so typeclass declarations
with/without = specify a partial order over types because the subset
relation is.

On Mon, Nov 14, 2011 at 3:47 AM, Patrick Browne patrick.bro...@dit.ie wrote:
 Is there a partial order on Haskell type classes?
 If so, does it induce any quasi-order relation on types named in the
 instances?
 In the example below types C and D have the same operation f
 Thanks,
 Pat

 data C = C deriving Show
 data D = D deriving Show

 class A t where
  f::t-t
  f t = t

 instance A C where
 instance A D where


 class A t = B t where

 instance B C where
 instance B D where

 ___
 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] Wondering if this could be done.

2010-11-22 Thread Ling Yang
Haskell does not play as well with overloading as one would do it in C++;
every
name used must be fully qualified.  Indeed, if we try something like

Indeed, if we try something like

data A = A Int deriving (Show, Eq)

test = A 3 unA (A i) = i

class Group a where (+) :: a - a - a

instance Group A where (+) x y = A $ unA x + unA y

we will get

Ambiguous occurrence `+'

It could refer to either `Main.+', defined at .hs:7:1
or `Prelude.+', imported from Prelude

Failed, modules loaded: none.

Haskell has its own brand of 'overloading': type classes. Every (+) sign
used
assumes that the operands are of the Num typeclass in particular. In order
to
define (+) on something else you will need to instance the Num typeclass
over
your A type.

I am not sure what you mean by the stuff defined in class Num is meanless
to
A. Strictly speaking nothing needs to be defined in a typeclass declaration
other than the required type signatures.

To instance the Num typeclass with A, though, assuming that A constructors
take
something that works with Num, you would do something similar to what Miguel
posted:

data A = A Int deriving (Show, Eq)

test = A 3 unA (A i) = i

instance Num A where (+) x y = A $ (unA x) + (unA y) (-) x y = A $ (unA x) -
(unA y) (*) x y = A $ (unA x) * (unA y) abs x = A $ (unA $ abs x) signum y =
A
$ (unA $ signum y) fromInteger i = A (fromInteger i)

Look at fromInteger, which must take Integer as as argument. That may be
inconvenient for you. The Awesome Prelude, referenced in Chris's post, is a
way
of defining less specific version of basic types like Bool so that you have
more choices in defining things like fromInteger in the Num typeclass (which
must take an Integer; it is 'sad' if that Integer refers to a grounded,
specific type).

Still, if not every one of the Num operations make sense for your A type,
you
can leave them blank and get a warning.

On Sun, Nov 21, 2010 at 10:48 PM, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Hi,
  For example, I have a data A defined. Then I want to add (+) and (-)
 operators to it, as a sugar (compared to addA/minusA). But * or other
 stuff defined in class Num is meanless to A. So I just do:
 (+) :: A - A - A
 (+) a b =
  A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
 the (+) is ambiguous.

  So, just wondering, does this way work in Haskell?
 --
 竹密岂妨流水过
 山高哪阻野云飞
 ___
 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] Re: Making monadic code more concise

2010-11-17 Thread Ling Yang
Thank you for highlighting these problems; I should really test my own code
more thoroughly. After reading these most recent examples, the translation
to
existing monads is definitely too neat, and a lot of semantics of the monad
are
'defaulted' on. In particular for the probability monad examples I see I had
the mistaken impression that it would preserve the random-world semantics of
the do-notation whereas autolifting actually imposes a random-evaluation
semantics, which would not be how I envision an autolifted probabilistic
DSL.

Overall, I think I pretty much got caught up in how cool it was going to be
to
use $, *, join/enter/exit as primitives to make any monad-based DSL work
'concisely' in an environment of existing typeclasses. That is kind of the
thing I want to do at a high level; implement DSLs like probabilistic
programming languages as primitives that that play transparently with
existing
expressions.

But now it seems clear to me that this autolifting approach will not be
useful
with any monad where it is important to control sharing and effects, which
is
critical in the probability monad (and all others I can think of); in fact
it
seems necessary to incur the do-notation 'overhead' (which I now see is not
overhead at all!) to work with them meaningfully at all, no matter how
'pure'
they look in other settings. Because of this we see that the Prob monad as
it
is defined here is mostly unusable with autolifting. Again, thanks for the
examples; I think I now have a much better intuition for do/bind and why
they
are required.

At this point, however, I would still want to see if it is possible to do
the
autolifting in a more useful manner, so that the user still has some control
over effects. Things like the share combinator in the paper you linked will
probably be very useful. I will definitely go over it in detail.

From my previous experience however, this might also be accomplished by
inserting something between the autolifting and the target monad.

I think it would be more helpful now to talk more about where I'm coming
from.
Indeed, the probability monad examples feature heavily here because I'm
coming
off of implementing a probabilistic programming language in Python that
worked
through autolifting, so expressions in it looked like host language
expressions. It preserved the random-world semantics because it was using a
quote-like applicative functor to turn a function composition in the
language
into an expression-tree rep of the same. I am not sure yet how to express it
in
Haskell (as I need to get more comfortable with GADTs), but pure would take
a
term to an abstract version of it, and fmap would take a function and
abstract
term to an abstract term representing the answer. One would then have the
call
graph available after doing this on lifted functions. I think of this as an
automatic way of performing the 'polymorphic embedding' referenced in

[Hofer et al 2008] Polymorphic Embedding of DSLs.

By keeping IDs on different abstract terms, expressions like X + X (where X
=
coin 0.5) would take the proper distributions under random-world semantics.

In general for monads where the control of sharing is important, it can be
seen
as limiting the re-running of effects to one per name. Each occurence of a
name
using the same unwrapped value.

I had the initial impression, now corrected, that I could just come up with
an
autolifting scheme in Haskell, use it with the usual probability monad and
somehow get this random-world semantics for free. No; control of sharing and
effects is in fact critical, but could be done through using the autolifting
as
a way to turn expressions into a form where control of them is possible.

For now, though, it looks like I have a lot of things to read through.

Again, thanks Oleg and everyone else for all the constructive feedback. This
definitely sets a personal record for misconceptions corrected / ideas
clarified per day.

On Wed, Nov 17, 2010 at 12:08 AM, o...@okmij.org wrote:


 Let me point out another concern with autolifting: it makes it easy to
 overlook sharing. In the pure world, sharing is unobservable; not so
 when effects are involved.

 Let me take the example using the code posted in your first message:

  t1 = let x = 1 + 2 in x + x

 The term t1 is polymorphic and can be evaluated as an Int or as a
 distribution over Int:


  t1r = t1 ::Int-- 6
  t1p = t1 ::Prob Int   -- Prob {getDist = [(6,1.0)]}

 That looks wonderful. In fact, too wonderful. Suppose later on we
 modify the code to add a non-trivial choice:

  t2 = let x = coin 0.5 + 1 in x + x
  -- Prob {getDist = [(4,0.25),(3,0.25),(3,0.25),(2,0.25)]}

 The result isn't probably what one expected. Here, x is a shared
 computation rather than a shared value. Therefore, in (x + x)
 the two occurrences of 'x' correspond to two _independent_ coin flips.
 Errors like that are insidious and very difficult to find. There are
 no overt problems, no exceptions are thrown, and the 

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

2010-11-16 Thread Ling Yang
Thanks Oleg for the feedback. If I understand right, there is a hard (as in
computability) limit for automatic instancing due to the general requirement of
deriving functions off of the behavior of another.

At this point, I wonder: How good are we at doing this? There's languages that
reside in the more expressive corners of the lambda cube, such as Epigram. Some
of the concepts have been translated to Haskell, such as Djinn. Are only
'trivial' results possible, or that the incomputability problems are just moved
into type space?

In any case, it's a good reason to limit the scope of autolifting.

On Tue, Nov 16, 2010 at 2:49 AM,  o...@okmij.org wrote:

 Ling Yang wrote
 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).

 In general, what this seems to be is a transformation on functions
 that also depends explicitly on type signatures. For example in Num:

 Things start to break down when we get to the higher order. In the first
 order, it is indeed easy to see that the monadification of the term
        Int - Int - Int
 should/could be
        m Int - m Int - m Int
 Indeed, liftM2 realizes this transformation. But what about
        (Int - Int) - Int
 ?
 Should it be
        (m Int - m Int) - m Int
 ?
 A moment of thought shows that there is no total function of the type

        Monad m = ((Int - Int) - Int) - ((m Int - m Int) - m Int)

 because there is no way, in general, to get from (m Int - m Int) to
 the pure function Int-Int. That is, we can't write
        Monad m = (m Int - m Int) - m (Int-Int)
 One may try tabulation (for finite domains)

 tf f = do
       vt - f (return True)
       vf - f (return False)
       return $ \x - if x then vt else vf

 but that doesn't quite work: what if the resulting function is never
 invoked on the True argument. We have needlessly computed that value,
 vt. Worse, we have incurred the effect of computing vt; that effect
 could be failure. We have needlessly failed.

 One can say: we need runnable

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

 are there many monads that are members of that typeclass? For example,
 Maybe cannot be Runnable; otherwise, what is (exit Nothing)? Any Error
 or MonadPlus monad can't be Runnable.

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


[Haskell-cafe] Making monadic code more concise

2010-11-15 Thread Ling Yang
Hi,

I'm fairly new to Haskell and recently came across some programming
tricks for reducing monadic overhead, and am wondering what
higher-level concepts they map to. It would be great to get some
pointers to related work.

Background:

I'm a graduate student whose research interests include methods for
implementing domain specific languages. Recently, I have been trying
to get more familiar with Haskell and implementing DSLs in it. I'm
coming from having a fair bit of experience in Python so I know the
basics of functional programming.

However, I'm much less familiar with Haskell. In particular I have
little to no internal map from existing DSL implementation techniques
to the Haskell extensions that would no doubt make DSL implementations
easier (and when they are *not* needed).

I also don't have a complete picture of the functional programming
research that would inform these techniques. I would greatly
appreciate it if I could get pointers to the appropriate references so
I can really get going on this.

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.

The probability monad is a good example.

import Control.Monad
import Data.List

newtype Prob a = Prob { getDist :: [(a, Float)] } deriving (Eq, Show)

multiply :: Prob (Prob a) - Prob a
multiply (Prob xs) = Prob $ concat $ map multAll xs
where multAll (Prob innerxs, p) = map (\(x, r) - (x, p * r)) innerxs

instance Functor Prob where
fmap f (Prob xs) = Prob $ map (\(x, p) - (f x, p)) xs

instance Monad Prob where
return x = Prob [(x, 1.0)]
x = f = multiply (fmap f x)

In this monad, = hides the multiplying-out of conditional
probabilities that happen during the composition of a random variable
with a conditional distribution.

coin x = Prob [(1, x), (0, 1 - x)]

test = do
x - (coin 0.5)
y - (coin 0.5)
return $ x + y

*Main test
Prob {getDist = [(2,0.25),(1,0.25),(1,0.25),(0,0.25)]}

We can use a 'sum out' function to get more useful results:

sumOut :: (Ord a) = Prob a - Prob a
sumOut (Prob xs) = Prob $ map (\kvs - foldr1 sumTwoPoints kvs) eqValues
where
eqValues = groupBy (\x y - (fst x == fst y)) $ sortBy compare 
xs
sumTwoPoints (v1, p1) (v2, p2) = (v1, p1 + p2)

*Main sumOut test
Prob {getDist = [(0,0.25),(1,0.5),(2,0.25)]}

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)

It seems what I'm leading into here is making functions on ordinary
values polymorphic over their monadic versions; I think this is the
desire for 'autolifting' or 'monadification' that has been mentioned
in works such as HaRE

http://www.haskell.org/pipermail/haskell/2005-March/015557.html

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 (/)

Note that already, even though each function in the typeclass had to
be manually lifted, this eliminates more overhead compared to lifting
every function used, because any function with a general enough type
bound can work with both monadic and non-monadic values, not just the
ones in the typeclass:

*Main sumOut $ (coin 0.5) + (coin 0.5) + (coin 0.5)
Prob {getDist = [(0,0.125),(1,0.375),(2,0.375),(3,0.125)]}
*Main let foo x y z = (x + y) * z
*Main sumOut $ foo (coin 0.5) (coin 0.5) (coin 0.5)
Prob {getDist = [(0,0.625),(1,0.25),(2,0.125)]}

Because of the implementation of fromInteger as return . fromInteger,
we also 'luck out' and have the ability to mix ordinary and
non-monadic values in the same expression:

*Main 1 + coin 0.5 / 2
Prob {getDist = [(1.5,0.5),(1.0,0.5)]}

My question is, what are the higher-level concepts at play here? The
motivation is that it should be possible to automatically do this
typeclass instancing, letting us get the benefits of concise monadic
expressions without manually instancing the typeclasses.

Indeed, I didn't have this idea in Haskell; I'm coming from Python
where one can realize the automatic instances: if we take the view
that classes in Python are combined datatypes and instanced
typeclasses, we can use the meta-object protocol to look inside one
class's representation and output another class with liftM-ed (or
return . -ed) methods and a custom constructor. I realize Template
Haskell gives you the ability to reify instance/class declarations,
but perhaps there's a 

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