Why I Love Haskell In One Simple Example

I posted this on my blog at http://changelog.complete.org/node/339 but I thought there may be some here that would find it of use. I recently implemented some new Haskell numeric types that, instead of performing calculations, can generate a rendering of the requested calculation or store units with it. Here you see a transcript of my session with a Haskell interpreter. The mathematical statements I am entering after the ">" are standard Haskell expressions, and, as I demonstrate, normally evaluate to a single result. Once I get a more powerful simplifier, I will probably write a LaTeX exporting function as well. The entire implementation of this, BTW, is less than 200 lines. NumTest> 5 + 1 * 3 8 NumTest> prettyShow $ 5 + 1 * 3 "5+(1*3)" NumTest> rpnShow $ 5 + 1 * 3 "5 1 3 * +" NumTest> prettyShow $ 5 + 1 * 3 "5+(1*3)" NumTest> prettyShow $ simplify $ 5 + 1 * 3 "5+3" NumTest> prettyShow $ 5 * (Symbol "x") + 3 "(5*x)+3" NumTest> 5 / 2 2.5 NumTest> (units 5 "m") / (units 2 "s") 2.5_m/s NumTest> (units 5 "m") / 2 2.5_m NumTest> 10 * (units 5 "m") / (units 2 "s") 25.0_m/s NumTest> sin (pi/2) 1.0 NumTest> sin (units (pi/2) "rad") 1.0_1.0 NumTest> sin (units 90 "deg") 1.0_1.0 NumTest> (units 50 "m") * sin (units 90 "deg") 50.0_m NumTest> ((units 50 "m") * sin (units 90 "deg")) :: Units (SymbolicManip Double) 50.0*sin(((2.0*pi)*90.0)/360.0)_m NumTest> rpnShow $ dropUnits $ ((units 50 "m") * sin (units 90 "deg")) "50.0 2.0 pi * 90.0 * 360.0 / sin *" NumTest> (units (Symbol "x") "m") * sin (units 90 "deg") x*sin(((2.0*pi)*90.0)/360.0)_m Also, I defined this in my source file: test :: forall a. (Num a) => a test = 2 * 5 + 3 Now, it can be used: NumTest> test 13 NumTest> rpnShow test "2 5 * 3 +" NumTest> prettyShow test "(2*5)+3" NumTest> test + 5 18 NumTest> prettyShow (test + 5) "((2*5)+3)+5" NumTest> rpnShow $ test + 5 "2 5 * 3 + 5 +" You can grab the very early experimental code with darcs get http://darcs.complete.org/num. Haskell has no built-in support for numeric types with units, arbitrary symbols carried through computations, etc. But it was trivial to add it. This kind of extensibility is a key part of why Haskell is so amazing.

I recently implemented some new Haskell numeric types that, instead of performing calculations, can generate a rendering of the requested calculation or store units with it.
good old Haskell rule (with apologies to Daniel Düsentrieb, I think;): "impossible things are delayed immediately, miracles may take a little longer" you can't get an expression representation from a value, but you can generate a representation while building the expression, so that you have it at hand if/when needed. I did something similar once (pairing values with representations instead of calculating values from representations), which you might find interesting for comparison (note that the focus in this one was on simplicity, eg. string representation only, no simplification, etc.): http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/R.hs btw, that kind of thing gets even more interesting with ho-functions like foldr, foldl, map. try it!-) nice for explaining these hofs.. (the code still works, but if you use ghci -fglasgow-exts instead of hugs +98, the defaulting doesn't seem to kick in, so you'll need to give explicit type annotations, eg. "map (+) [1..4::R Integer]" or "foldl (-) 0 [1..4::R Integer]"). cheers, claus --------------------------------------------------------------------------------------- Do you have late-breaking research results in FP but have missed the other deadlines? Submit to TFP'05: http://www.tifp.org/tfp05/ --------------------------------------------------------------------------------------- extended abstracts: 8th July 2005 <==== full papers: 2nd September 2005 symposium: 23/24 September 2005, Tallinn, Estonia (w.ICFP/GPCE) ---------------------------------------------------------------------------------------

Hi John <snip>
Also, I defined this in my source file:
test :: forall a. (Num a) => a test = 2 * 5 + 3
Now, it can be used:
NumTest> test 13 NumTest> rpnShow test "2 5 * 3 +" NumTest> prettyShow test "(2*5)+3" NumTest> test + 5 18 <snip>
I had newer seen anybody use "forall a." in function signatures before, and therefore was curious about its effect. This is probably do to my inexperience regarding Haskell. However, I tried to remove it and wrote this instead: test :: (Num a) => a and the code still compiled and seems to run fine. Also using the prettyShow and rpnShow functions. So, why are you using the forall keyword? (this is not meant as a critique, i am just curious) I tried to find documentation about the use of the forall keyword in respect to functions (I do know about it in with respect to existentially quantified types), but with no luck. So, if anybody has some good pointers, please let med know about it. /Mads Lindstrøm

On 2005-06-27, Mads Lindstrøm
Hi John
test :: forall a. (Num a) => a test = 2 * 5 + 3
[ snip ]
I had newer seen anybody use "forall a." in function signatures before, and therefore was curious about its effect. This is probably do to my inexperience regarding Haskell. However, I tried to remove it and wrote this instead:
If you omit it, the compiler will decide that test is some arbitrary type (Double, Integer, whatever). While rpnShow, etc. will still work, they will not show you the same thing, since the compiler will have already "optimized" the expression down to one set type. Which compiler or interpreter are you using?
I tried to find documentation about the use of the forall keyword in respect to functions (I do know about it in with respect to existentially quantified types), but with no luck. So, if anybody has some good pointers, please let med know about it.
Note that test in this example is not a function. -- John

Hi John Goerzen
On 2005-06-27, Mads Lindstrøm
wrote: Hi John
test :: forall a. (Num a) => a test = 2 * 5 + 3
[ snip ]
I had newer seen anybody use "forall a." in function signatures before, and therefore was curious about its effect. This is probably do to my inexperience regarding Haskell. However, I tried to remove it and wrote this instead:
If you omit it, the compiler will decide that test is some arbitrary type (Double, Integer, whatever). While rpnShow, etc. will still work, they will not show you the same thing, since the compiler will have already "optimized" the expression down to one set type. They show the same thing on my computer, namely
"2 5 * 3 +" if I do ":type test" I get (with or without the forall a.): rpnShow :: Num a => SymbolicManip a -> String
Which compiler or interpreter are you using?
hugs -98 :version -- Hugs Version November 2003 I have not tried with ghc(i), as it would not load MissingH.Str. Some problem I will have to look into later.
I tried to find documentation about the use of the forall keyword in respect to functions (I do know about it in with respect to existentially quantified types), but with no luck. So, if anybody has some good pointers, please let med know about it.
Note that test in this example is not a function.
OK, I assumed it was, as I thought all functions started with lower case and all modules, classes, and data/type constructors started with upper case. It does not take any variables as input, but that is still a function in my book (but I could be wrong there. I am no mathematician).
-- John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
note that I am not using: test :: a -- this will actually not compile or not giving any type signatur, but using: test :: (Num a) => a /Mads Lindstrøm

On Mon, 2005-06-27 at 22:12 +0200, Mads Lindstrøm wrote:
I had newer seen anybody use "forall a." in function signatures before, and therefore was curious about its effect. This is probably do to my inexperience regarding Haskell.
The "forall a." syntax is not Haskell 98. The universal quantification of type variables is implicit in type signatures for polymorphic functions, so there is no need to write it. Haskell extensions have gone beyond the polymorphism allowed in Haskell 98, and thus have needed to disambiguate different types with explicit quantifiers. Hence, glasgow-exts and hugs -98 allow an explicit forall.
If you omit it, the compiler will decide that test is some arbitrary type (Double, Integer, whatever).
I think John is talking about the monomorphism restriction and defaulting. The use of the forall syntax is orthogonal to this.
Note that test in this example is not a function. OK, I assumed it was, as I thought all functions started with lower case and all modules, classes, and data/type constructors started with upper case. It does not take any variables as input, but that is still a function in my book (but I could be wrong there. I am no mathematician).
This kind of declaration: f = rhs is called a "pattern binding" in Haskell. In contrast to this kind of declaration: g pat1 pat2 ... patn = rhs which is called a function binding. g is always a function, but f might be bound to a constant expression, or it might be bound to a function. Now, for convenience, people might say f and g are functions, even when f is bound to a constant expression. Here's where it gets tricky: pattern bindings can be overloaded (so can function bindings, but they are less tricky). When a pattern binding is overloaded it is as if it has an implicit argument, which corresponds to a type class dictionary (a structure that contains concrete implementations of the classes overloaded functions). In that situation you can imagine that the bound variable is a function whose (only) argument is the dictionary - only you don't pass it in explicitly, the compiler adds it for you. This brings us to the monomorphism restriction, which John was talking about. This rule says that a pattern binding is not allowed to be overloaded unless you supply an explicit type signature that says it is overloaded. I won't go into the justification for this (it is a contentious point, read the Haskell Report if you like). Cheers, Bernie.

foo :: Num a => a -> a -> a foo x y = x + z where z = 2 * y Now since adding type signatures is a good thing, you want to give z an explicit type signature. But |z :: a| fails with an "Inferred type is less polymorphic than expected" error because the |a| actually means |forall a. a| and not the |a| from foo's type signature. The classical way (still, it's an extension implemented in hugs and all versions of ghc i'm aware of) to bring the in scope by binding it like
Hi Mads, Since ghc-6.4 there's another feature that is enabled by such explicit foralls in type signatures, namely scoped type variables. Consider this:
foo (x :: a) y = x + y where This is fine in such simple examples, but often gets tedious and clutters up the definition by weird type annotations. Therefore ghc-6.4 implements the great feature that the |a| from foo's type signature is automatically brought into scope if you explicitely quantify it with a forall.
Aside: A small disadvantage seems to be that you can only scope over either all or none of the type variables in your signature. However,
foo :: forall a. Num a => (forall b. ...) will bring the variable a into scope, but not b and is otherwise equivalent to foo :: forall a b. Num a => ...
On 6/27/05, Mads Lindstrøm
I had newer seen anybody use "forall a." in function signatures before, and therefore was curious about its effect. This is probably do to my inexperience regarding Haskell. However, I tried to remove it and wrote this instead:
test :: (Num a) => a
and the code still compiled and seems to run fine. Also using the prettyShow and rpnShow functions. So, why are you using the forall keyword? (this is not meant as a critique, i am just curious)
I tried to find documentation about the use of the forall keyword in respect to functions (I do know about it in with respect to existentially quantified types), but with no luck. So, if anybody has some good pointers, please let med know about it. A great recource is http://haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html Bookmark this page and come back to it every once in a while - there are just so many treasures in it - one of my favorites is "7.4.12. Generalised derived instances for newtypes"
Thomas
participants (5)
-
Bernard Pope
-
Claus Reinke
-
John Goerzen
-
Mads Lindstrøm
-
Thomas Jäger