Re: [Haskell-cafe] Proposal: Applicative => Monad: Call for consensus

Hi Tyson (So OT, I'm switching to cafe.) On 19 Jan 2011, at 18:24, Tyson Whitehead wrote:
On January 17, 2011 16:20:22 Conor McBride wrote:
Ahem
: )
The unfortunate pain you pay for this additional power is manually having to specify the application (<$> and <*>) and merging (join). If the compiler could figure this all out for you based on the underlying types, wow!
To achieve such a thing, one would need to ensure a slightly more deliberate separation of "value" and "computation" in the presentation of types. In Haskell, we use, e.g., [Int], for
* pure computations of lists of integers * nondeterministic computations of integers
[..]
I'm pretty sure I know what "pure computations of lists of integers" is, but I'm not so sure about "nondeterministic computations of integers".
If it is not too much of an effort, could you clarify with a quick example?
Viewing [] as a monad, you can view [1,2] as a nondeterministic integer with possible values 1 and 2. Lifting operations to this monad gives you "all possible combinations" computation, so, as SHE would have it, (| [1,2] + [3,4] |) = pure (+) <*> [1,2] <*> [3,4] = [4,5,5,6] It's not hard to come up with examples where lifted and unlifted both make sense. With a bit of help from Twitter, we have (courtesy of Andy Gimblett) (["under","over"] ++ ["state","wear"]) = ["under","over","state","wear"] but (|["under","over"] ++ ["state","wear"]|) = ["understate","underwear","overstate","overwear"] and (courtesy of Dan Piponi) (["plan","tan"] ++ ["gent","king"]) = ["plan","tan","gent","king"] but (|["plan","tan"] ++ ["gent","king"]|) = ["plangent","planking","tangent","tanking"] In each case, the former has (++) acting on lists of strings as pure values, while the latter has (++) acting on strings as values given in []-computations. The type [String] determines a domain, it does not decompose uniquely to a notion of computation and a notion of value. We currently resolve this ambiguity by using one syntax for pure computations with [String] values and a different syntax for [] computations with String values. Just as we use newtypes to put a different spin on types which are denotationally the same, it might be worth considering a clearer (but renegotiable) separation of the computation and value aspects of types, in order to allow a syntax in which functions are typed as if they act on *values*, but lifted to whatever notion of computation is ambient. After types for representation, let us have types for explanation. All the best Conor

On January 19, 2011 15:28:33 Conor McBride wrote:
In each case, the former has (++) acting on lists of strings as pure values, while the latter has (++) acting on strings as values given in []-computations.
The type [String] determines a domain, it does not decompose uniquely to a notion of computation and a notion of value. We currently resolve this ambiguity by using one syntax for pure computations with [String] values and a different syntax for [] computations with String values.
Just as we use newtypes to put a different spin on types which are denotationally the same, it might be worth considering a clearer (but renegotiable) separation of the computation and value aspects of types, in order to allow a syntax in which functions are typed as if they act on *values*, but lifted to whatever notion of computation is ambient.
Yes. That makes sense. Thank you both for the clarification. The idea of explicitly separating the two aspects of types is an interesting one. The automated approach I had been thinking of was to always take the simplest context possible. (i.e., for the above, list of strings as pure values). To this end I've been working on a measure for the complexity of the application operator. I've got a draft at http://www.sharcnet.ca/~tyson/haskell/papers/TypeShape.pdf I'm still working on my thinking on polymorphic types though, so everything from section 2.2 onwards is subject to change (especially 2.3 and the conclusion). Cheers! -Tyson

Interesting little paper, Tyson.
You bring up other programming languages and 'ad-hoc systems for
resolving ambiguities'; I agree with you that these systems generally
have no strong theoretical basis, but I'm not sure that's a terribly
bad thing.
I think what a programmer actually wants from ambiguity resolution is
something *predictable*; C++'s system is definitely stretching the
boundaries of predictability, but any case where I have to break out a
calculator to decide whether the compiler is going to choose
specification A or specification B for my program seems like a
failure. I'd much rather the solution wasn't always 'the most
probable' but at least was easy for me to figure out without thinking
too hard.
The goal is to easily know when I have to manually specify ambiguity
resolution and when I can trust the compiler to do it for me. I
didn't completely follow the math in your paper, so maybe it turns out
simply if it was implemented, but it wasn't clear to me. At the
least, I think you should add examples of the types of ambiguity
resolution you'd like the compiler to figure out and what your
probability measure chooses as the correct answer in each case.
Anyways, thanks for the interesting read. I'm excited to see work on
making a better type *inference* system, since much of the work lately
seems to be on making a better *type* system at the cost of more often
manually specifying types.
I work in a traditional programming industry, and most of the people
from work that I talk to about Haskell are frustrated that they can't
just write putStrLn (readLn + (5 :: Int)) and have the compiler figure
out where the lifts and joins go. After all, that just works in C[1]!
What's the point of having the most powerful type system in the
universe if the compiler can't use it to make your life easier?
-- ryan
[1] sample program:
int readLn(); // reads a line from stdin and converts string to int
void putStrLn(int x); // prints an int to stdout
void main() { putStrLn(readLn() + 5); }
On Fri, Jan 21, 2011 at 8:43 AM, Tyson Whitehead
On January 19, 2011 15:28:33 Conor McBride wrote:
In each case, the former has (++) acting on lists of strings as pure values, while the latter has (++) acting on strings as values given in []-computations.
The type [String] determines a domain, it does not decompose uniquely to a notion of computation and a notion of value. We currently resolve this ambiguity by using one syntax for pure computations with [String] values and a different syntax for [] computations with String values.
Just as we use newtypes to put a different spin on types which are denotationally the same, it might be worth considering a clearer (but renegotiable) separation of the computation and value aspects of types, in order to allow a syntax in which functions are typed as if they act on *values*, but lifted to whatever notion of computation is ambient.
Yes. That makes sense. Thank you both for the clarification. The idea of explicitly separating the two aspects of types is an interesting one.
The automated approach I had been thinking of was to always take the simplest context possible. (i.e., for the above, list of strings as pure values).
To this end I've been working on a measure for the complexity of the application operator. I've got a draft at
http://www.sharcnet.ca/~tyson/haskell/papers/TypeShape.pdf
I'm still working on my thinking on polymorphic types though, so everything from section 2.2 onwards is subject to change (especially 2.3 and the conclusion).
Cheers! -Tyson
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

uj supplied this: About the discussion "putStrLn (readLn + (5 :: Int))".. I'll write it as the following line, importing Control.Applicative main = (+) readLn (return 3) They look almost exactly same in my eyes.. On Fri, 21 Jan 2011 11:01:36 -0800, you wrote:
Interesting little paper, Tyson.
You bring up other programming languages and 'ad-hoc systems for resolving ambiguities'; I agree with you that these systems generally have no strong theoretical basis, but I'm not sure that's a terribly bad thing.
I think what a programmer actually wants from ambiguity resolution is something *predictable*; C++'s system is definitely stretching the boundaries of predictability, but any case where I have to break out a calculator to decide whether the compiler is going to choose specification A or specification B for my program seems like a failure. I'd much rather the solution wasn't always 'the most probable' but at least was easy for me to figure out without thinking too hard.
The goal is to easily know when I have to manually specify ambiguity resolution and when I can trust the compiler to do it for me. I didn't completely follow the math in your paper, so maybe it turns out simply if it was implemented, but it wasn't clear to me. At the least, I think you should add examples of the types of ambiguity resolution you'd like the compiler to figure out and what your probability measure chooses as the correct answer in each case.
Anyways, thanks for the interesting read. I'm excited to see work on making a better type *inference* system, since much of the work lately seems to be on making a better *type* system at the cost of more often manually specifying types.
I work in a traditional programming industry, and most of the people from work that I talk to about Haskell are frustrated that they can't just write putStrLn (readLn + (5 :: Int)) and have the compiler figure out where the lifts and joins go. After all, that just works in C[1]! What's the point of having the most powerful type system in the universe if the compiler can't use it to make your life easier?
-- ryan
[1] sample program: int readLn(); // reads a line from stdin and converts string to int void putStrLn(int x); // prints an int to stdout
void main() { putStrLn(readLn() + 5); }
On Fri, Jan 21, 2011 at 8:43 AM, Tyson Whitehead
wrote: On January 19, 2011 15:28:33 Conor McBride wrote:
In each case, the former has (++) acting on lists of strings as pure values, while the latter has (++) acting on strings as values given in []-computations.
The type [String] determines a domain, it does not decompose uniquely to a notion of computation and a notion of value. We currently resolve this ambiguity by using one syntax for pure computations with [String] values and a different syntax for [] computations with String values.
Just as we use newtypes to put a different spin on types which are denotationally the same, it might be worth considering a clearer (but renegotiable) separation of the computation and value aspects of types, in order to allow a syntax in which functions are typed as if they act on *values*, but lifted to whatever notion of computation is ambient.
Yes. ?That makes sense. ?Thank you both for the clarification. ?The idea of explicitly separating the two aspects of types is an interesting one.
The automated approach I had been thinking of was to always take the simplest context possible. ?(i.e., for the above, list of strings as pure values).
To this end I've been working on a measure for the complexity of the application operator. ?I've got a draft at
http://www.sharcnet.ca/~tyson/haskell/papers/TypeShape.pdf
I'm still working on my thinking on polymorphic types though, so everything from section 2.2 onwards is subject to change (especially 2.3 and the conclusion).
Cheers! ?-Tyson
_______________________________________________ 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 -- Regards, Casey

On Fri, Jan 21, 2011 at 7:58 PM, Casey Hawthorne
uj supplied this:
About the discussion "putStrLn (readLn + (5 :: Int))"..
I'll write it as the following line,
importing Control.Applicative main = (+) readLn (return 3)
They look almost exactly same in my eyes..
You're missing some bits. main = print =<< liftM2 (+) readLn (return 3) Which I assert looks like more line noise than some perl programs I've read. :) Now, you *can* get away with simplifying this to main = print =<< (readLn :: IO Int) + 3 assuming instance Num a => Num (IO a), which sort-of works (show instance and pattern matching are both quite broken; given the naive implementation of fib, fib readLn will give you quite a surprising result!) But I think this case proves the point quite well: it's a special case where Num turns out to be very friendly. Why can't the whole language be that friendly? -- ryan

On Tue, Jan 25, 2011 at 05:13, Ryan Ingram
On Fri, Jan 21, 2011 at 7:58 PM, Casey Hawthorne
wrote: uj supplied this:
About the discussion "putStrLn (readLn + (5 :: Int))"..
I'll write it as the following line,
importing Control.Applicative main = (+) readLn (return 3)
They look almost exactly same in my eyes..
You're missing some bits.
main = print =<< liftM2 (+) readLn (return 3)
Which I assert looks like more line noise than some perl programs I've read. :)
Why not just: main = print . (+3) =<< readLn This reads almost as well as a function composition f . g . h, I think. Erik P.S. I wanted to say you could also write it left-to-right using >>> from Control.Arrow, but that need parentheses: main = readLn >>= ((+3) >>> print)

Erik Hesselink
importing Control.Applicative
main = print =<< liftM2 (+) readLn (return 3) [...] line noise
Why not just:
main = print . (+3) =<< readLn
Or using applicative: print =<< (+3) <$> readLn ? (Which separates the printing from the addition.) -k -- If I haven't seen further, it is by standing in the footprints of giants

On Tue, Jan 25, 2011 at 10:20 AM, Ketil Malde
Erik Hesselink
writes: importing Control.Applicative
main = print =<< liftM2 (+) readLn (return 3) [...] line noise
Why not just:
main = print . (+3) =<< readLn
Or using applicative:
print =<< (+3) <$> readLn
?
(Which separates the printing from the addition.)
-k
IMHO, all these proposed solutions just serve to further illustrate the problem. :-) Personally I don't mind having to use explicit combinators to interact with monadic values -- forces me to think things through, and all that -- but it's true that having automatic lifting would be convenient, and look less syntaxy. Alternatively, Disciple has effect typing and strictness-by-default rather than IO/ST monads, meaning you can use the same combinators to control functions with effects as you would for non-effectful functions, which is sort of like having automatic lifting for the IO and ST monads but not anything else (besides being a lot finer-grained).
-- If I haven't seen further, it is by standing in the footprints of giants
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

On Tue, 2011-01-25 at 12:17 +0100, Gábor Lehel wrote:
On Tue, Jan 25, 2011 at 10:20 AM, Ketil Malde
wrote: Erik Hesselink
writes: importing Control.Applicative
main = print =<< liftM2 (+) readLn (return 3) [...] line noise
Why not just:
main = print . (+3) =<< readLn
Or using applicative:
print =<< (+3) <$> readLn
?
(Which separates the printing from the addition.)
-k
IMHO, all these proposed solutions just serve to further illustrate the problem. :-)
Even SHE? main = (| print (| readLn + ~5 |) @|) int main () { print ("%d\n", readLn () + 5); } Looks rather similar (except noise of both languages).
Personally I don't mind having to use explicit combinators to interact with monadic values -- forces me to think things through, and all that -- but it's true that having automatic lifting would be convenient, and look less syntaxy.
class Debug m where debug :: Show a => m a -> m a instance Debug (Writer [String]) where debug x = tell (show x) instance Debug IO where debug = print instance (Show w, Show a) => Show (Writer w) where -- Yes I'm using old mtl to illustrate the problem show (Writer (a, w)) = "Writer (" ++ show a ++ ", " ++ show w ++ ")" main = debug (return (return ())) *> return () What does it do? - In case of no lifting it prints "Writer ((), [])" - In case of lifting it may mean "debug <$> return (return ())" which would not print anything Regards

On 25 January 2011 09:20, Ketil Malde
(+3) <$> readLn
This is how I'd like it. import Control.Applicative(pure,liftA2) main = print =<< pure 3 <+> readLn where (<+>) = liftA2 (+) Just a matter of taste I suppose. And about auto-lifting, I vaguely remember reading something about possible different denotations it could lead to, but I can't find it now. Ozgur

On Mon, 2011-01-24 at 20:13 -0800, Ryan Ingram wrote:
On Fri, Jan 21, 2011 at 7:58 PM, Casey Hawthorne
wrote: uj supplied this:
About the discussion "putStrLn (readLn + (5 :: Int))"..
I'll write it as the following line,
importing Control.Applicative main = (+) readLn (return 3)
They look almost exactly same in my eyes..
You're missing some bits.
main = print =<< liftM2 (+) readLn (return 3)
Which I assert looks like more line noise than some perl programs I've read. :)
Or using idiom brackets (for example from SHE): main = print =<< (| readLn + ~3 |) or main = (| print (| readLn + ~3 |) @|) Regards

On January 21, 2011 14:01:36 Ryan Ingram wrote:
Interesting little paper, Tyson.
Hi Ryan, Thanks for comments and kind words.
I think what a programmer actually wants from ambiguity resolution is something *predictable*; C++'s system is definitely stretching the boundaries of predictability, but any case where I have to break out a calculator to decide whether the compiler is going to choose specification A or specification B for my program seems like a failure. I'd much rather the solution wasn't always 'the most probable' but at least was easy for me to figure out without thinking too hard.
I think you really hit the nail on the head there. To be useful at all, it is absolutely critical that you don't have to reach for your calculator. Fortunately I believe this is the case. The basic result of the paper was that assuming - self-similarity (functional programming) and - finite-length (typed programs) you get p(n) = 1 / 2^{2n-1) as the probability of a specific shape composed of n elementary components. Note that the measure is defined on the shape: the way elementary types are composed, not what they are. Double and Char are indistinguishable from a shapes perspective, Int -> Double -> Char and (Int -> Double) -> Char are not. An example of the probabilities give same types (shapes) would then be Double: p(1) = 1/2 (elementary components: Double) Char: p(1) = 1/2 (elementary components: Char) [Int]: p(2) = 1/8 (elementary components: [], Int) [Char] -> IO (): p(5) = 1/512 (elementary components: [], Char, ->, IO, ()) As p(n) is monotonically decreasing function in n, the more elementary types the shape is composed of, the less probable it is. I really don't think there could be a much more pleasing result in terms of a predictable measure. It is very simple, and I believe it corresponds well to our intuition. The more stuff in a type, the more complex it is. It may seem strange to have went to such ends for such a simple result, but that is just because these simple examples don't show the depth. Specifically - we gained the ability to encode the intuition into a piece of software, and - we can now go beyond where our intuition starts to break down. To see this last point, consider the shapes represented by Double vs Double -> Int. The formulation says the former shape will arise more frequently in programs, and I imagine we agree. But are we more likely to see the shape (a -> b - > a) -> a -> [b] -> a where a and b are place holders for any internal shape, or Int -> Char -> Int Suddenly it is not so easy for us. The former is a more complex composition, but it is also a less rigid composition. The formulation has no such problem.
The goal is to easily know when I have to manually specify ambiguity resolution and when I can trust the compiler to do it for me. I didn't completely follow the math in your paper, so maybe it turns out simply if it was implemented, but it wasn't clear to me. At the least, I think you should add examples of the types of ambiguity resolution you'd like the compiler to figure out and what your probability measure chooses as the correct answer in each case.
The specific ambiguous situation I was looking at resolving when I came up with the framework was figuring out what application operator to use. Consider various applications incorporating a computation context c (e.g., []) \f -> f :: (a -> b) -> a -> b \f -> fmap f :: (a -> b) -> c a -> c b \f -> f . pure :: (c a -> b) -> a -> b \f -> apply f :: c (a -> b) -> c a -> c b \f -> apply f . pure :: c (a -> b) -> (a -> c b) \f -> apply f . pure . pure :: c (c a -> b)) -> a -> c b \f -> join . func f :: (a -> c b) -> c a -> c b \f -> join . apply f :: c (a -> c b) -> c a -> c b \f -> join . apply f . pure :: c (a -> c b) -> a -> c b \f -> join . apply f . pure . pure :: c (ca -> cb) -> a -> c b where I've listed them in order of increasing structure requirements on c (the bottom four requiring a monad, the prior three require applicative, etc.) In any one situation, more than one application may be possible (such as the "under", "over", "state", "wear" example mentioned by Conor). I want a rigorous argument for ordering these to follow the least surprise principal. I probably should be more specific about this in the paper, but I really liked the framework, and didn't want to pigeon hole it to this specific application. Cheers! -Tyson
participants (9)
-
Casey Hawthorne
-
Conor McBride
-
Erik Hesselink
-
Gábor Lehel
-
Ketil Malde
-
Maciej Piechotka
-
Ozgur Akgun
-
Ryan Ingram
-
Tyson Whitehead