Recursion in Haskell

Hi I understand the basic principle of recursion but have difficulty with the following: -- a recursive function -- for calculating the length of lists myLen [] = 0 myLen (x:xs) = 1 + myLen xs What's happening here? Top marks for a comprehensive jargon-free explanation. Thanks in advance Paul

On Feb 17, 2007, at 21:32 , P. R. Stanley wrote:
Hi I understand the basic principle of recursion but have difficulty with the following: -- a recursive function -- for calculating the length of lists myLen [] = 0 myLen (x:xs) = 1 + myLen xs What's happening here?
This definition uses pattern matching. The first one matches an empty list; the second matches a list using constructor syntax (a list [a,b,c] in constructor syntax is a:b:c:[]) in order to extract the first element and the rest of the list into separate variables "x" and "xs", then recursively invokes itself on xs. The "x" being unused, that definition can also be rewritten as: myLen (_:xs) = 1 + myLen xs since _ can be used in a pattern match as a placeholder. -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

prstanley:
Hi I understand the basic principle of recursion but have difficulty with the following: -- a recursive function -- for calculating the length of lists
myLen [] = 0 myLen (x:xs) = 1 + myLen xs
So this is a definition for the 'length' function on lists. The list data structure is defined as: data [a] = [] | a : [a] Some specific lists: Prelude> [] [] Prelude> 1 : [] [1] Prelude> 1 : 2 : [] [1,2] Now, functions can "pattern match" on their arguments, to access the fields inside the data structure. Pattern matching lets you take apart data structures. For example, we can implement the head and tail functions on lists as: head [] = error "empty list" head (x:xs) = x tail [] = error "empty list" tail (x:xs) = xs Note how we write a case for both variants of the list data type, one case for the empty list, and one case for the cons node. Now, we are in a position to write the length function on lists: Either, a list is empty, in which case its length is 0: length [] = 0 or, the inductive case, it contains at least one value, and the tail of a list. Then the length is 1 + the length of the tail: length (x:xs) = 1 + length xs And that's it. You can avoid naming variables in patterns that you don't use, with the wildcard pattern: length (_:xs) = 1 + length xs Cheers, Don

Brandon, Chris, Don, gentlemen, Thank you all for your swift and well-written answers. I should point out that I'm coming to functional programming with a strong background in programming in C and C-type languages. I am also very new to the whole philosophy of functional programming. Hence my bafflement at some of the very elementary attributes of Haskell. I thought that would give you chaps a better idea of where I'm coming from with my queries. Back to mylen. Here is the definition once more: mylen [] = 0 mylen (x:y) = 1 + mylen y The base case, if that is the right terminology, stipulates that the recursion ends with an empty list and returns 0. Simple though one question - why does mylen require the parentheses even when it is evaluating the length of [...]? I can understand the need for them when dealing with x:... because of the list construction function precedence but not with [2,3,etc]. I thought a [e] was treated as a distinct token. I'm assuming that the interpreter/compiler is equipped to determine the type and value of xs subsequent to which it calls itself and passes the object minus the first element as argument unless the object is an empty list. going back to Don's formal definition of the list data structure: data [a] = [] | a : [a] A list is either empty or contains an element of type a? Correct, wrong or very wrong? By the way, what branch of discrete math - other than the obvious ones such as logic and set theory - does functional programming fall under? Many thanks in advance for your help Paul

On Feb 18, 2007, at 21:26 , P. R. Stanley wrote:
mylen (x:y) = 1 + mylen y The base case, if that is the right terminology, stipulates that the recursion ends with an empty list and returns 0. Simple though one question - why does mylen require the parentheses even when it is evaluating the length of [...]? I can understand the need for them when dealing with x:... because of the list construction
Because it would expect three parameters without the parentheses. ":" is a perfectly valid variable name; the convention in Haskell is that such names represent infix functions, but this is only a convention. The ability to use such names is convenient when passing operators or functions as parameters (this is, after all, functional programming!). BTW, it might also help to understand how mylen is rewritten by the compiler: mylen xx = case xx of [] -> 0 (x:xs) -> 1 + mylen xs ("xx" being actually an internal identifier which will never conflict with any name you use)
going back to Don's formal definition of the list data structure: data [a] = [] | a : [a] A list is either empty or contains an element of type a? Correct, wrong or very wrong?
Either empty, or an "a" consed with (the ":" is pronounced "cons") a list of "a". This is a recursive definition. "a" is an unspecified type; the formal definition allows any number (including zero, via []) of values of the same unspecified type to be combined into a list recursively as a : a : a : ... : []. The [a,a,a...] syntax is a convenient alternative syntax for a:a:a:...:[]; the two forms are completely equivalent, but the cons syntax is more convenient for pattern matching a list as (head:tail). -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

P. R. Stanley wrote:
Brandon, Chris, Don, gentlemen, Thank you all for your swift and well-written answers. I should point out that I'm coming to functional programming with a strong background in programming in C and C-type languages. I am also very new to the whole philosophy of functional programming. Hence my bafflement at some of the very elementary attributes of Haskell. I thought that would give you chaps a better idea of where I'm coming from with my queries. Back to mylen. Here is the definition once more: mylen [] = 0 mylen (x:y) = 1 + mylen y The base case, if that is the right terminology, stipulates that the recursion ends with an empty list and returns 0. Simple though one question - why does mylen require the parentheses even when it is evaluating the length of [...]? I can understand the need for them when dealing with x:... because of the list construction function precedence but not with [2,3,etc]. I thought a [e] was treated as a distinct token.
I'm assuming that the interpreter/compiler is equipped to determine the type and value of xs subsequent to which it calls itself and passes the object minus the first element as argument unless the object is an empty list.
I think what you're asking here is why you need the parens around (x:y) in the second case. Function application doesn't use parentheses, but it has a very high precedence, so "mylen x:y" would be parsed as "(mylen x) : y", since the ":" constructor has a lower precedence.
going back to Don's formal definition of the list data structure: data [a] = [] | a : [a] A list is either empty or contains an element of type a? Correct, wrong or very wrong?
A list is either empty, or consists of the first object, which is of type a (just called "a" here) and the rest of the list, which is also a list of type a (called "[a]" here). The syntax is an impediment to understanding here; a clearer version of the list type would be data List a = Empty | Cons a (List a) The left-hand case says that a list can be just Empty. The right-hand case says that a list can also be a "Cons" of a value of type a (the first element) and a List of type a (the rest of the list). So, for instance, in my definition these are all lists: Empty Cons 10 Empty -- list of Int Cons 10 (Cons 20 Empty) Cons "foo" (Cons "bar" (Cons "baz" Empty)) -- list of String Using normal Haskell lists these are: [] 10 : Empty -- also written as [10] 10 : 20 : Empty -- also written as [10, 20] "foo" : "bar" : "baz" : Empty -- also written as ["foo", "bar", "baz"] The list syntax e.g. [1, 2, 3] is just syntactic sugar; the "real" syntax would be with the : operator e.g. 1 : 2 : 3 : []. We use the sugar because it's easier to read and write.
By the way, what branch of discrete math - other than the obvious ones such as logic and set theory - does functional programming fall under?
The usual answer to this is "category theory" which is an extremely abstract branch of mathematics. But you don't really need to know category theory to program in Haskell (though it helps for reading Haskell papers). Also, lambda calculus is useful, and there is a field called "type theory" which is also useful. Pierce's book _Types and Programming Languages_ will get you up to speed on lambda calculus and type theory, though it doesn't use Haskell. Mike

On Feb 18, 2007, at 21:44 , Michael Vanier wrote:
I think what you're asking here is why you need the parens around (x:y) in the second case. Function application doesn't use parentheses
Function application never applies to pattern matching.
The usual answer to this is "category theory" which is an extremely abstract branch of mathematics. But you
Actually, no; my understanding is that category theory as applied to Haskell is a retcon introduced when the notion of monads was imported from category theory, and the original theoretical foundation of Haskell came from a different branch of mathematics. Lambda calculus is pretty fundamental to Haskell or any functional programming language, as is type theory (although that you really don't have to understand in detail unless you're hacking the type system; most of us leave that to Oleg :) and the Curry-Howard isomorphism (simply stated: computer programs can be converted into mathematical proofs, and vice versa; this is most clearly demonstrated when the programs are described in terms of the lambda calculus, which is where the original formulation of Curry-Howard came from). -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Feb 18, 2007, at 21:44 , Michael Vanier wrote:
I think what you're asking here is why you need the parens around (x:y) in the second case. Function application doesn't use parentheses
Function application never applies to pattern matching.
You're right; I take it back. However, ":" is not an acceptable variable name as such either: ghci> let foo x : y = x <interactive>:1:4: Parse error in pattern ":" needs to be surrounded by parens to be treated as a function; otherwise it's an operator. OK, we can try: ghci> let foo x (:) y = x <interactive>:1:10: Constructor `:' should have 2 arguments, but has been given 0 In the pattern: : In the definition of `foo': foo x : y = x Bottom line: "foo x:y" is not a valid pattern.
The usual answer to this is "category theory" which is an extremely abstract branch of mathematics. But you
Actually, no; my understanding is that category theory as applied to Haskell is a retcon introduced when the notion of monads was imported from category theory, and the original theoretical foundation of Haskell came from a different branch of mathematics.
Nevertheless, a lot of Haskell papers do refer to category theory, and lambda calculus can be put into that framework as well, so I don't think my statement is invalid. But as you say, it's a bit of an after-the-fact realization. Mike

Chaps, is there another general pattern for mylen, head or tail? mylen [] = 0 mylen (x:xs) = 1 + mylen (xs) head [] = error "what head?" head (x:xs) = x tail [] = error "no tail" tail (x:xs)= xs This pattern matching reminds me of a module on formal spec I studied at college. What are the pre-requisites for Lambda calculus? Thanks Paul

P. R. Stanley wrote:
What are the pre-requisites for Lambda calculus? Thanks Paul
Learning lambda calculus requires no prerequisites other than the ability to think clearly. However, don't think that you need to understand all about lambda calculus in order to learn Haskell. It's more like the other way around: by the time you've learned Haskell, you've already unwittingly absorbed a good deal of lambda calculus. Once again, I recommend Pierces _Types and Programming Languages_ as a reference if you really feel you need to learn this now. For absorbing the functional style of programming (which is what you really should be working on at this point), the book _Structure and Interpretation of Computer Programs_ by Abelson and Sussman (which uses Scheme, not Haskell) is very valuable. For learning about recursion, the book _The Little Schemer_ by Friedman and Felleisen is also very good (and quite short); it also uses Scheme. However, most of the insights of both books carry over into Haskell (with a change of syntax, of course). Mike

Michael Vanier wrote:
P. R. Stanley wrote:
What are the pre-requisites for Lambda calculus? Thanks Paul
Learning lambda calculus requires no prerequisites other than the ability to think clearly. However, don't think that you need to understand all about lambda calculus in order to learn Haskell. It's more like the other way around: by the time you've learned Haskell, you've already unwittingly absorbed a good deal of lambda calculus. Once again, I recommend Pierces _Types and Programming Languages_ as a reference if you really feel you need to learn this now.
For absorbing the functional style of programming (which is what you really should be working on at this point), the book _Structure and Interpretation of Computer Programs_ by Abelson and Sussman (which uses Scheme, not Haskell) is very valuable. For learning about recursion, the book _The Little Schemer_ by Friedman and Felleisen is also very good (and quite short); it also uses Scheme. However, most of the insights of both books carry over into Haskell (with a change of syntax, of course
How to Design Programs (HtDP) www.htdp.org is another Scheme teaching text that is lower level, slower paced. It may be too low level for you, i.e. rather boring, or it may be helpful. I'd definitely recommend reading SICP after it. Programming Languages: Application and Interpretation (PLAI) http://www.cs.brown.edu/~sk/Publications/Books/ProgLangs/ is a good book for either before or after SICP (which is also available online at http://mitpress.mit.edu/sicp/). All of these use Scheme, but most of it uses a very "functional" style and it should transfer to Haskell very easily, especially the PLAI one. It would be very nice to see a HtDP-style online book for Haskell; none of the currently available introductions really fit this role in my opinion.

For absorbing the functional style of programming (which is what you really should be working on at this point),
For functional style and the reasoning attitude associated with lazy functional programming, the following book is a good introduction: @Book{Bird-2000, author = {Richard Bird}, title = {Introduction to Functional Programming using {Haskell}}, year = 2000, publisher = {Prentice-Hall} } This is the second edition of: @Book{Bird-Wadler-1988, year = 1988, title = {Introduction to Functional Programming}, publisher = {Prentice-Hall}, author = {Richard Bird and Phil Wadler} } Wolfram

On Feb 18, 2007, at 22:22 , P. R. Stanley wrote:
is there another general pattern for mylen, head or tail?
Those are basically it, aside from optionally replacing the unused variables with _.
What are the pre-requisites for Lambda calculus?
Lambda calculus isn't related to what's normally called "calculus"; while some basic math and logic are useful, you don't really need much of a formal or complex math background to unravel it. See for example the early parts of http://en.wikipedia.org/wiki/ Lambda_calculus for an introduction. (The later parts quickly become hard to digest until you've understood the earlier ones; the Wikipedia article is more a reference than an introduction.) -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

P. R. Stanley wrote:
Chaps, is there another general pattern for mylen, head or tail? mylen [] = 0 mylen (x:xs) = 1 + mylen (xs)
head [] = error "what head?" head (x:xs) = x
tail [] = error "no tail" tail (x:xs)= xs
There are of course stylistic variations possible, e.g. you can use case instead of pattern bindings: mylen list = case list of [] -> 0 (x:xs) -> 1 + mylen (xs) As you see, this moves pattern matching from the lhs to the rhs of the equation. Another very common 'pattern' is to factor the recursion into a generic higher order function fold op z [] = z fold op z (x:xs) = x `op` (fold op z xs) -- parentheses not strictly necessary here, added for readability and define mylen in terms of fold mylen = fold (+) 0 You also have the possibility to use boolean guards as in mylen xs | null xs = 0 | otherwise = 1 + mylen (tail xs) (Although here we use the more primitive functions (null) and (tail) which in turn would have to be defined using pattern matching. Pattern matching is the only way to examine data of which nothing is known other than its definition.) Lastly, there are cases where you want to use nested patterns. For instance, to eliminate successive duplicates you could write elim_dups (x:x':xs) = if x == x' then xs' else x:xs' where xs' = elim_dups (x':xs) elim_dups xs = xs Here, the first clause matches any list with two or more elements; the pattern binds the first element to the variable (x), the second one to (x'), and the tail to (xs). The second clause matches everything else, i.e. empty and one-element lists and acts as identity on them.
This pattern matching reminds me of a module on formal spec I studied at college.
As long as your code doesn't (have to) use a tricky algorithm (typically if the algorithm is more or less determined by the data structure, as in the above examples) then it is really like an executable specification. Cheers Ben

P. R. Stanley:
is there another general pattern for mylen, head or tail? mylen [] = 0 mylen (x:xs) = 1 + mylen (xs)
head [] = error "what head?" head (x:xs) = x
tail [] = error "no tail" tail (x:xs)= xs
Benjamin Franksen:
Another very common 'pattern' is to factor the recursion into a generic higher order function
fold op z [] = z fold op z (x:xs) = x `op` (fold op z xs) -- parentheses not strictly necessary here, added for readability
and define mylen in terms of fold
mylen = fold (+) 0
Looks more like a sum than a length. Benjamin really meant something like this: mylen = fold (const succ) 0 Note, the Prelude already contains various fold functions, so you don't have to write your own. The one corresponding to fold is "foldr". (Benjamin just wrote it out to demonstrate the practice of extracting and naming reusable computational structures as higher-order functions). Now, can you write head as a fold? Would you want to? What about tail?

The definition of myLen says:
myLen [] = 0 The length for an empty list is zero
myLen (x:xs) = 1 + myLen xs The length of a list containing x and some other stuff (xs) is 1 + (the length of the other stuff).
So basically, if you've got a list [1,2,3], it will try to do this:
myLen (1:[2,3]) = 1 + myLen [2,3] The length of [1,2,3] is 1 + the length of [2,3]
myLen (2:[3]) = 1 + myLen [3] The length of [2,3] = 1 + the length of [3]
myLen (3:[]) = 1 + myLen [] This is the tricky part, now the other case of myLen is being called:
myLen [] = 0 Here you can see that it won't recurse anymore. Now there is going to be some replacement:
myLen (3:[]) can now be calculated, because "myLen []" is now known (0). Because we know this,
myLen (2:[3]) can now be calculated too, because we know that myLen [3] is 1. And so on.
I think the trick here is to see that "[1]" is exactly the same as "1: []". Once you grasp this, the rest will probably easy. Good luck! -chris On 17 Feb, 2007, at 19:32 , P. R. Stanley wrote:
Hi I understand the basic principle of recursion but have difficulty with the following: -- a recursive function -- for calculating the length of lists myLen [] = 0 myLen (x:xs) = 1 + myLen xs What's happening here? Top marks for a comprehensive jargon-free explanation. Thanks in advance Paul
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (9)
-
Benjamin Franksen
-
Brandon S. Allbery KF8NH
-
Chris Eidhof
-
Derek Elkins
-
dons@cse.unsw.edu.au
-
kahl@cas.mcmaster.ca
-
Matthew Brecknell
-
Michael Vanier
-
P. R. Stanley