ANN: First Monad Tutorial of the Season

Hello All, I'm proud to announce the first monad tutorial of the new season. It's under the Wiki permissive licence, but the web page has some clip art, so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on http://www.muitovar.com/monad/moncow.xhtml Best Regards, Hans van Thiel

Hans van Thiel wrote:
I'm proud to announce the first monad tutorial of the new season. It's under the Wiki permissive licence, but the web page has some clip art, so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on http://www.muitovar.com/monad/moncow.xhtml
"First, let's talk about prefix, infix and postfix. Suppose you want to put the argument of a unary function after the function (postfix)." You mean 'before', not 'after'. Cheers Ben

Hans van Thiel wrote:
so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on http://www.muitovar.com/monad/moncow.xhtml
Forgot to say: nicely written! Some more comments: You can declare a fixity (infixr) for flop instead of using parentheses (yes, this is allowed; see 'elem' in the Prelude). Would make the code more readable. "(Recall that a type definition is just like a data definition, but with no choice operator (|).)" First, you mean to say 'newtype', not 'type' (as in the code). Second, a newtype may also contain only one data element (i.e. one type expression after the constructor), not many, as in a data type definition. Third, newtype is unlifted. Cheers Ben

On Mon, 2008-08-25 at 00:33 +0200, Ben Franksen wrote:
Hans van Thiel wrote:
so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on http://www.muitovar.com/monad/moncow.xhtml
Forgot to say: nicely written!
Some more comments:
You can declare a fixity (infixr) for flop instead of using parentheses (yes, this is allowed; see 'elem' in the Prelude). Would make the code more readable.
"(Recall that a type definition is just like a data definition, but with no choice operator (|).)" First, you mean to say 'newtype', not 'type' (as in the code). Thanks for the feedback. If and when I get some more comments and error reports, I'll try to fix them. Second, a newtype may also contain only one data element (i.e. one type expression after the constructor), not many, as in a data type definition. Yes, that's what I thought too, but then I got confused by State s a, which looks to have two. Could you explain?
Third, newtype is unlifted. The books I use for reference, the Craft and SOE, don't seem to mention this. I have to confess, I don't really understand the difference between newtype and data. Again, an explanation would be appreciated.
As a general comment on the teaching of Haskell, all books and tutorials, which I've seen, appear to treat this aspect of Haskell as if it were self explanatory. This while the better known imperative languages don't have anything like it. Only Real World Haskell explains algebraic data types to some satisfaction (IMHO, of course). Best Regards, Hans

On Mon, Aug 25, 2008 at 5:33 AM, Hans van Thiel
The books I use for reference, the Craft and SOE, don't seem to mention this. I have to confess, I don't really understand the difference between newtype and data. Again, an explanation would be appreciated.
A newtype has no run-time representation; it is an entity at type-checking time, nothing more. data, on the other hand, has a runtime representation.
data D = D Int newtype N = N Int
d1 = D 1 n1 = N 1 i1 = 1 :: Int
In memory at runtime, these look different; n1 looks exactly the same as i1. We can represent them both in this way: lit = 1 :: Int# (unlifted, unboxed int) i1 = { tag = I#, content -> lit } n1 = { tag = I#, content -> lit } But d1 is different; it looks like this: d1 = { tag = D, content -> i1 } There's an extra level of indirection between the "data" version and the contents. What does this mean? Well, in particular, you get different behavior in a couple of cases when dealing with "error" (or infinite loops):
u = error "u" du = D (error "du") nu = N (error "nu")
ignoreD (D _) = "ok!" ignoreN (N _) = "ok!"
ignoreD u => error "u" ignoreN u => "ok!" ignoreD looks for the "D" tag on its argument, which forces its argument to be evaluated. That fails and you get an error. But "unwrapping" the newtype doesn't do anything; it's just there for typechecking. So there is no error in that case. -- ryan

ryani.spam:
On Mon, Aug 25, 2008 at 5:33 AM, Hans van Thiel
wrote: The books I use for reference, the Craft and SOE, don't seem to mention this. I have to confess, I don't really understand the difference between newtype and data. Again, an explanation would be appreciated.
A newtype has no run-time representation; it is an entity at type-checking time, nothing more. data, on the other hand, has a runtime representation.
data D = D Int newtype N = N Int
d1 = D 1 n1 = N 1 i1 = 1 :: Int
In memory at runtime, these look different; n1 looks exactly the same as i1. We can represent them both in this way:
lit = 1 :: Int# (unlifted, unboxed int) i1 = { tag = I#, content -> lit } n1 = { tag = I#, content -> lit }
But d1 is different; it looks like this:
d1 = { tag = D, content -> i1 }
There's an extra level of indirection between the "data" version and the contents. What does this mean? Well, in particular, you get different behavior in a couple of cases when dealing with "error" (or infinite loops):
Though the D tag will be represented as a bit set on the bottom of the thunk pointer in GHC (useful to remember). 'data' tags are cheap.

Hans van Thiel wrote:
On Mon, 2008-08-25 at 00:33 +0200, Ben Franksen wrote:
Hans van Thiel wrote:
so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on http://www.muitovar.com/monad/moncow.xhtml
"(Recall that a type definition is just like a data definition, but with no choice operator (|).)" First, you mean to say 'newtype', not 'type' (as in the code). Thanks for the feedback. If and when I get some more comments and error reports, I'll try to fix them. Second, a newtype may also contain only one data element (i.e. one type expression after the constructor), not many, as in a data type definition. Yes, that's what I thought too, but then I got confused by State s a, which looks to have two. Could you explain?
Most probably you are confusing type and data constructor. This is a common error and a hurdle I remember falling over more than once. It is due to the fact that in Haskell both are in completely separate name spaces, nevertheless both use capitalized names. Thus people often use the same name for both, especially with newtype, as there may only be one data constructor. In your case you have newtype State s a = State { runState :: (s -> (a, s)) } where the type constructor takes two (type-) arguments (even for a newtype it can take as many as you like), but the data constructor takes only one value as argument, namely a function from s to (a,s). Clear now?
Third, newtype is unlifted. The books I use for reference, the Craft and SOE, don't seem to mention this. I have to confess, I don't really understand the difference between newtype and data. Again, an explanation would be appreciated.
Did Ryan's explanation help?
As a general comment on the teaching of Haskell, all books and tutorials, which I've seen, appear to treat this aspect of Haskell as if it were self explanatory. This while the better known imperative languages don't have anything like it. Only Real World Haskell explains algebraic data types to some satisfaction (IMHO, of course).
This is one of the more difficult aspects Haskell, IME. I found the Haskell wiki book (http://en.wikibooks.org/wiki/Haskell) very useful, especially the chapter on denotational semantics (http://en.wikibooks.org/wiki/Haskell/Denotational_semantics). If you have a background in imperative languages, especially low-level ones like C, then it may help to think of the values of a lifted type (data ...) as being represented by a pointer to the data proper (e.g. a struct), whereas values of an unlifted type (newtype ...) are represented exactly as the argument type. A value of a lifted type always has one additional value in its type, namely bottom. You may think of bottom as being represented by a null pointer. In fact, one could say that, in Java, Objects are always lifted whereas basic types like integer are unlifted. Now, before I get shot down by the purists, I know that this is not exactly true, since bottom is also the value of an infinite loop, so Java in fact has a 'real' bottom in addition to null, etc. See the above cited online book chapter for a more precise (and still very readable) treatment. Cheers Ben

[snip]
Most probably you are confusing type and data constructor. This is a common error and a hurdle I remember falling over more than once. It is due to the fact that in Haskell both are in completely separate name spaces, nevertheless both use capitalized names. Thus people often use the same name for both, especially with newtype, as there may only be one data constructor. In your case you have
newtype State s a = State { runState :: (s -> (a, s)) }
where the type constructor takes two (type-) arguments (even for a newtype it can take as many as you like), but the data constructor takes only one value as argument, namely a function from s to (a,s).
Clear now?
A newtype has only one data constructor, a data definition may have more (when it contains a choice (|) operator). That's clear now.
Third, newtype is unlifted. The books I use for reference, the Craft and SOE, don't seem to mention this. I have to confess, I don't really understand the difference between newtype and data. Again, an explanation would be appreciated.
Did Ryan's explanation help?
As a general comment on the teaching of Haskell, all books and tutorials, which I've seen, appear to treat this aspect of Haskell as if it were self explanatory. This while the better known imperative languages don't have anything like it. Only Real World Haskell explains algebraic data types to some satisfaction (IMHO, of course).
This is one of the more difficult aspects Haskell, IME. I found the Haskell wiki book (http://en.wikibooks.org/wiki/Haskell) very useful, especially the chapter on denotational semantics (http://en.wikibooks.org/wiki/Haskell/Denotational_semantics).
The wikibook has a lot of good material, IMO. I'll certainly read that chapter.
If you have a background in imperative languages, especially low-level ones like C, then it may help to think of the values of a lifted type (data ...) as being represented by a pointer to the data proper (e.g. a struct), whereas values of an unlifted type (newtype ...) are represented exactly as the argument type. That makes sense to me. Thanks, everybody! A value of a lifted type always has one additional value in its type, namely bottom. You may think of bottom as being represented by a null pointer. In fact, one could say that, in Java, Objects are always lifted whereas basic types like integer are unlifted.
Now, before I get shot down by the purists, I know that this is not exactly true, since bottom is also the value of an infinite loop, so Java in fact has a 'real' bottom in addition to null, etc. See the above cited online book chapter for a more precise (and still very readable) treatment.
Cheers Ben

Hans van Thiel wrote:
As a general comment on the teaching of Haskell, all books and tutorials, which I've seen, appear to treat this aspect of Haskell as if it were self explanatory. This while the better known imperative languages don't have anything like it. Only Real World Haskell explains algebraic data types to some satisfaction (IMHO, of course).
(Hopefully this different take on it helps more than it hurts...) In addition to keeping the type-level and the value-level separated, Haskell does a little bit to keep the type/interface-level and the implementation-level separate. The "data" keyword introduces both a new type and also a new implementation. This is the only way of introducing new implementations. ADTs are beauty incarnate, but unfortunately not well known outside of functional languages and abstract algebra. The "newtype" keyword introduces a new type, but it reuses an old implementation under the covers. Even though they have the same underlying implementation, the newtype and the type of the old implementation are considered entirely different semantically and so one cannot be used in lieu of the other. The dubiously named "type" keyword introduces an alias shorthand for some type that already exists. These aliases are, in a sense, never checked; that is, the macro is just expanded. This means that we can't carry any additional semantic information by using aliases and so if we have: type Celsius = Int type Fahrenheit = Int ...the type checker will do nothing to save us. If we wanted to add semantic tags to the Int type in order to say what units the number represents, then we could do that with a "newtype" and the type checker would ensure that we didn't mix units. Re "data" vs "newtype", where a newtype is possible (single data constructor, which has exactly one argument) there are still a few differences at the semantic level. Since a newtype's data constructor doesn't exist at runtime, evaluating a newtype to WHNF will evaluate the argument to WHNF; hence a newtype can be thought of as the data version with an obligatory strictness annotation. In terms of bottom, this means that: data Foo = Foo Int ...has both _|_ and (Foo _|_). Whereas, both of the following: data Foo = Foo !Int newtype Foo = Foo Int ...have only _|_. It should also be noted that the overhead for newtypes is not *always* removed. In particular, if we have the following definitions: data Z = Z newtype S a = S a We must keep the tags (i.e. boxes) for S around because (S Z) and (S (S Z)) need to be distinguishable. This only really comes up with polymorphic newtypes (since that enables recursion), and it highlights the difference between strict fields and unpacked strict fields. Typically newtypes are unpacked as well as strict (hence no runtime tag overhead), but it's not guaranteed. Another operational difference between newtypes and an equivalent data declaration has to do with the type class dictionaries. IIRC, with GeneralizedNewtypeDeriving the newtype actually uses the exact same dictionaries as the underlying type, thus avoiding unwrapping/rewrapping overhead. I'm somewhat fuzzy on all the details here, bit its another reason to use newtypes when you can. -- Live well, ~wren

On Tue, Aug 26, 2008 at 1:19 AM, wren ng thornton
It should also be noted that the overhead for newtypes is not *always* removed. In particular, if we have the following definitions:
data Z = Z newtype S a = S a
We must keep the tags (i.e. boxes) for S around because (S Z) and (S (S Z)) need to be distinguishable. This only really comes up with polymorphic newtypes (since that enables recursion), and it highlights the difference between strict fields and unpacked strict fields. Typically newtypes are unpacked as well as strict (hence no runtime tag overhead), but it's not guaranteed.
Is this true? (S Z) and (S (S Z)) only need to be distinguished during typechecking. This would be different if it was some sort of existential type:
newtype N = forall a. Num a => N a but GHC at least disallows existential boxes in newtypes.
-- ryan

Ryan Ingram wrote:
wren ng thornton wrote:
It should also be noted that the overhead for newtypes is not *always* removed. In particular, if we have the following definitions:
data Z = Z newtype S a = S a
We must keep the tags (i.e. boxes) for S around because (S Z) and (S (S Z)) need to be distinguishable. This only really comes up with polymorphic newtypes (since that enables recursion), and it highlights the difference between strict fields and unpacked strict fields. Typically newtypes are unpacked as well as strict (hence no runtime tag overhead), but it's not guaranteed.
Is this true? (S Z) and (S (S Z)) only need to be distinguished during typechecking.
This would be different if it was some sort of existential type:
newtype N = forall a. Num a => N a but GHC at least disallows existential boxes in newtypes.
From my experiments looking at memory usage, the above declarations take
They only need to be distinguished at type checking time, true; but if you have a function that takes peano integers (i.e. is polymorphic over Z and (S a) from above) then you need to keep around enough type information to know which specialization of the function to take. The problem is that the polymorphism means that you can't do full type erasure because there's a type variable you need to keep track of. the same amount of memory as a pure ADT, which means linear in the value of the peano integer. It may be that I misinterpreted the results, but I see no other way to deal with polymorphic newtypes so I'm pretty sure this is what's going on. -- Live well, ~wren

The values Z, S Z, and S (S Z) all have the same runtime
representation and there is no linear increase in size when you add a
extra S.
BUT, if you make something overloaded and there is a dictionary
associated with the type (Z, S Z, or S (S Z)) then the dictionary
takes up space, and that space is linear in the number of S
constructors.
-- Lennart
On Tue, Aug 26, 2008 at 6:39 PM, wren ng thornton
Ryan Ingram wrote:
wren ng thornton wrote:
It should also be noted that the overhead for newtypes is not *always* removed. In particular, if we have the following definitions:
data Z = Z newtype S a = S a
We must keep the tags (i.e. boxes) for S around because (S Z) and (S (S Z)) need to be distinguishable. This only really comes up with polymorphic newtypes (since that enables recursion), and it highlights the difference between strict fields and unpacked strict fields. Typically newtypes are unpacked as well as strict (hence no runtime tag overhead), but it's not guaranteed.
Is this true? (S Z) and (S (S Z)) only need to be distinguished during typechecking.
This would be different if it was some sort of existential type:
newtype N = forall a. Num a => N a but GHC at least disallows existential boxes in newtypes.
They only need to be distinguished at type checking time, true; but if you have a function that takes peano integers (i.e. is polymorphic over Z and (S a) from above) then you need to keep around enough type information to know which specialization of the function to take. The problem is that the polymorphism means that you can't do full type erasure because there's a type variable you need to keep track of.
From my experiments looking at memory usage, the above declarations take the same amount of memory as a pure ADT, which means linear in the value of the peano integer. It may be that I misinterpreted the results, but I see no other way to deal with polymorphic newtypes so I'm pretty sure this is what's going on.
-- Live well, ~wren
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
The values Z, S Z, and S (S Z) all have the same runtime representation and there is no linear increase in size when you add a extra S.
BUT, if you make something overloaded and there is a dictionary associated with the type (Z, S Z, or S (S Z)) then the dictionary takes up space, and that space is linear in the number of S constructors.
Ah yes, that makes more sense. Since your instance would look like: instance Foo a => Foo (S a) where foo :: a -> Int a dictionary for Foo (S(S Z)) would have entries for foo@(S(S Z)) and also the dictionary for Foo (S Z) which has foo@(S Z) and a dictionary for Foo Z which has... It's still something to watch out for if you're really worrying about performance. I wonder if this is documented on the wiki's section about performance anywhere, the overhead for inductive type class instances I mean. -- Live well, ~wren
participants (6)
-
Ben Franksen
-
Don Stewart
-
Hans van Thiel
-
Lennart Augustsson
-
Ryan Ingram
-
wren ng thornton