[Wadler 89] Philip Wadler. "Theorems for free!": Can't get the same results in Haskell

Hi there, I was reading "Real World Haskell" and found this paper. [1] On the first page of the paper there is an example: inc* (odds_Int [1,2,3]) = [2,4] /= [4] = odds_Int (inc* [1,2,3]) I tried to implement it in Haskell: (I'm a newbie. I guess it's possible to write a better version.) module Param where import Prelude odds :: [Int] -> [Int] odds [] = [] odds [x] = if odd x then [x] else [] odds (x:xs) = if odds [x] == [] then odds xs else [x] ++ odds xs inc :: [Int] -> [Int] inc [] = error "Empty list" inc [x] = [succ x] inc (x:xs) = inc [x] ++ inc xs Looks fine: *Param> odds [1,2,3] [1,3] *Param> inc [1,2,3] [2,3,4] But my results differ from the paper's: *Param> inc (odds [1,2,3]) [2,4] *Param> odds (inc [1,2,3]) [3] I doubt that there is an error in the paper. So it seems that something is wrong with my code. But I can't find the error. Could you help me? (Or there is no error at all and I misunderstood something.) [1] http://ttic.uchicago.edu/~dreyer/course/papers/wadler.pdf Thanks

It looks to me like Wadler made a typo. Even great minds like his slip up
like that sometimes. However, I do have some comments below on your code.
On Aug 9, 2012 8:53 PM, "Stayvoid"
I tried to implement it in Haskell: (I'm a newbie. I guess it's possible to write a better version.)
module Param where import Prelude
The prelude is imported automatically. You only need to mention it as an import if you need to *avoid* importing some functions, or want some functions to be imported only "qualified". This is done if you want to use a name that clashes with one in the prelude. You'll see things like import Prelude hiding (foldl',foldl, foldr) import Prelude qualified as P in a module implementing a data structure that supports folds.
odds :: [Int] -> [Int] odds [] = []
This is a very awkward approach. There's no reason to have a special case for the one-element list, and certainly no reason to use ++ to add a single element to the front of a list. You should do the work in the (x:xs) case instead: odds [] = [] odds (x:xs) | odd x = x : odds xs | otherwise = odds xs In fact, there's a function called "filter" that captures this pattern, so you can even write: odds = filter odd
odds [x] = if odd x then [x] else [] odds (x:xs) = if odds [x] == [] then odds xs else [x] ++ odds xs
inc :: [Int] -> [Int] inc [] = error "Empty list" inc [x] = [succ x] inc (x:xs) = inc [x] ++ inc xs
Again, this is bizarre. You should be writing: inc [] = [] inc (x:xs) = succ x : inc xs Again, there is a function that captures this pattern, so you can shorten it to inc = map succ
Looks fine:
*Param> odds [1,2,3] [1,3] *Param> inc [1,2,3] [2,3,4]
But my results differ from the paper's:
*Param> inc (odds [1,2,3]) [2,4] *Param> odds (inc [1,2,3]) [3]
I doubt that there is an error in the paper.
I don't.
participants (2)
-
David Feuer
-
Stayvoid