question about styles of recursion

In RWH, in the exercises at the end of the book, I was told to write a function that averages the integer values in a list. I wanted to do this using on the tools we had been presented, which did not include 'length'. So I thought of writing a recursive function in which each case passes an accumulator of the "sum so far" as well as a count of node "up to the point", and the base case does the actual division. I was wondering if there is a better way of doing it (using the just ideas up to chapter 3, so no length, no higher order functions, no foldr/foldl or map). myAvg' :: Int -> [Int] -> [ Double ] -> Double myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs myAvg :: [Double] -> Double myAvg xs = myAvg' 0 0 xs Thanks, Mike

On Thu, Mar 26, 2009 at 09:19:18AM -0700, Michael Mossey wrote:
myAvg' :: Int -> [Int] -> [ Double ] -> Double myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
The definition of myAvg' looks fine, but I think you have the wrong type signature there.
myAvg :: [Double] -> Double myAvg xs = myAvg' 0 0 xs
You could also do it without accumulating parameters, like this: myAvg xs = sum / count where (sum, count) = sumCount xs sumCount :: [Double] -> (Double, Int) sumCount [] = (0,0) sumCount (x:xs) = (s+x, c+1) where (s,c) = sumCount xs -Brent

Michael Mossey
In RWH, in the exercises at the end of the book,
There are no exercises at the end of the book.
I was told to write a function that averages the integer values in a list. I wanted to do this using on the tools we had been presented, which did not include 'length'.
Ok. That sounds like you are working on the exercises for chapter 3 on p.69, specifically exercise 3. The length function was introduced before the sum function, which I see you are using in your function definition. See p. 15. The length function was also mentioned in exercise 1, and the instructions for exercise 3 mention using the length of the list.
So I thought of writing a recursive function in which each case passes an accumulator of the "sum so far" as well as a count of node "up to the point", and the base case does the actual division. I was wondering if there is a better way of doing it (using the just ideas up to chapter 3, so no length, no higher order functions, no foldr/foldl or map).
myAvg' :: Int -> [Int] -> [ Double ] -> Double myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
Use variables that are defined? Prelude Data.List> :load ehask.hs [1 of 1] Compiling Main ( ehask.hs, interpreted ) ehask.hs:3:44: Not in scope: `n' Failed, modules loaded: none.

7stud
myAvg' :: Int -> [Int] -> [ Double ] -> Double myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
The length function was introduced before the sum function, which I see you are using in your function definition.
Hmm...I guess you aren't using the sum function--that's one of your variable names. I wonder how Prelude knows sum is a variable name and not the sum function? I changed the name sum to s, and I get this error: Prelude Data.List> :load ehask.hs [1 of 1] Compiling Main ( ehask.hs, interpreted ) ehask.hs:2:24: Couldn't match expected type `Double' against inferred type `Int' In the expression: s / fromIntegral count In the definition of `myAvg'': myAvg' s count [] = s / fromIntegral count Failed, modules loaded: none.

Am Donnerstag 26 März 2009 21:53:47 schrieb 7stud:
7stud
writes: myAvg' :: Int -> [Int] -> [ Double ] -> Double myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
The length function was introduced before the sum function, which I see you are using in your function definition.
Hmm...I guess you aren't using the sum function--that's one of your variable names. I wonder how Prelude knows sum is a variable name and not the sum function?
Name shadowing/scoping. By naming one of the parameters sum, a local variable with that name is declared and Prelude.sum is only accessible qualified in that scope. It's the same as declaring local variables with the same name as one in an enclosing scope in other languages.
I changed the name sum to s, and I get this error:
Prelude Data.List> :load ehask.hs [1 of 1] Compiling Main ( ehask.hs, interpreted )
ehask.hs:2:24: Couldn't match expected type `Double' against inferred type `Int' In the expression: s / fromIntegral count In the definition of `myAvg'': myAvg' s count [] = s / fromIntegral count Failed, modules loaded: none.
Yup, the type signature is wrong, it should be myAvg' :: Double -> Int -> [Double] -> Double

Daniel Fischer
myAvg' :: Int -> [Int] -> [ Double ] -> Double
myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
ehask.hs:2:24: Couldn't match expected type `Double' against inferred type `Int' In the expression: s / fromIntegral count In the definition of `myAvg'': myAvg' s count [] = s / fromIntegral count Failed, modules loaded: none.
Yup, the type signature is wrong, it should be
myAvg' :: Double -> Int -> [Double] -> Double
Can you explain the error message in detail? To me it looks like this should be the problem: Prelude> fromIntegral [1, 2, 3] <interactive>:1:0: No instance for (Integral [t]) arising from a use of `fromIntegral' at <interactive>:1:0-21 Possible fix: add an instance declaration for (Integral [t]) In the expression: fromIntegral [1, 2, 3] In the definition of `it': it = fromIntegral [1, 2, 3]

Am Freitag 27 März 2009 03:37:27 schrieb 7stud:
Daniel Fischer
writes: myAvg' :: Int -> [Int] -> [ Double ] -> Double
myAvg' sum count [] = sum / fromIntegral count myAvg' sum count (x:xs) = myAvg' (x + sum) (n + 1) xs
ehask.hs:2:24: Couldn't match expected type `Double' against inferred type `Int' In the expression: s / fromIntegral count In the definition of `myAvg'': myAvg' s count [] = s / fromIntegral count Failed, modules loaded: none.
Yup, the type signature is wrong, it should be
myAvg' :: Double -> Int -> [Double] -> Double
Can you explain the error message in detail? To me it looks like this should be the problem:
Prelude> fromIntegral [1, 2, 3]
<interactive>:1:0: No instance for (Integral [t]) arising from a use of `fromIntegral' at <interactive>:1:0-21 Possible fix: add an instance declaration for (Integral [t]) In the expression: fromIntegral [1, 2, 3] In the definition of `it': it = fromIntegral [1, 2, 3]
That would be the next problem. By the type signature, the result of myAvg' is a Double, hence the use of (/) in the first equation is at type Double -> Double -> Double. Now the first argument of (/) is s(um), which by the type signature is of type Int, while (/) expects Double. So, expected type is Double, 'inferred' (from the type signature) type is Int, doesn't match, boom. The compiler stops there, if it didn't, it would also report the missing instance for (Integral [Int]).

Daniel Fischer
(/) in the first equation is at type Double -> Double -> Double.
Then why don't I get an error here: Prelude> 2 / 4 0.5 Prelude> 2 / fromIntegral 4 0.5 And why does this happen: Prelude> let x = 2 Prelude> :type x x :: Integer Prelude> x / fromIntegral 4 <interactive>:1:0: No instance for (Fractional Integer) arising from a use of `/' at <interactive>:1:0-17 Possible fix: add an instance declaration for (Fractional Integer) In the expression: x / fromIntegral 4 In the definition of `it': it = x / fromIntegral 4 And how do I read this type: Prelude> :type fromIntegral fromIntegral :: (Num b, Integral a) => a -> b What does the => mean?

On Fri, Mar 27, 2009 at 09:12:46AM +0000, 7stud wrote:
Daniel Fischer
writes: (/) in the first equation is at type Double -> Double -> Double.
Then why don't I get an error here:
Prelude> 2 / 4 0.5
There are several things going on here. The first is that numeric literals are overloaded; integral numeric literals (like 2) can be of any numeric type. What actually happens is that they get wrapped in a call to fromIntegral. The other thing going on is ghci's type defaulting: since it doesn't otherwise know what type this expression should be, it picks Double. (It would also pick Integer if that worked, but Integer doesn't work here because of the (/).)
Prelude> 2 / fromIntegral 4 0.5
From the above discussion you can see that this is exactly the same as the first expression.
And why does this happen:
Prelude> let x = 2 Prelude> :type x x :: Integer
This is because of the defaulting again. Since there are no constraints on the type of x this time, it picks Integer.
Prelude> x / fromIntegral 4
<interactive>:1:0: No instance for (Fractional Integer) arising from a use of `/' at <interactive>:1:0-17 Possible fix: add an instance declaration for (Fractional Integer) In the expression: x / fromIntegral 4 In the definition of `it': it = x / fromIntegral 4
Of course, now that x has type Integer, this is not well-typed; you can't divide Integers.
And how do I read this type:
Prelude> :type fromIntegral fromIntegral :: (Num b, Integral a) => a -> b
What does the => mean?
The => indicates class constraints. You can read this as "fromIntegral has type a -> b, as long as b is an instance of the Num class, and a is an instance of the Integral class." That is, fromIntegral can convert a value of any Integral type (Int, Integer) to a value of any Num type. -Brent

7stud wrote:
Michael Mossey
writes: In RWH, in the exercises at the end of the book,
There are no exercises at the end of the book.
Thanks for the help everyone. I wrote this post in the middle of the night when I had some insomnia, and I had just taken a sleeping medication, so I was basically "drunk." It's like trying to program drunk. My apologies for screwing up so many aspects of the post, but the gist of my question was answered, I think. Before I go further, let me ask again: can someone show me how to put the "School of Expression" code "on the library path" so I don't have to put it in the same directory where I'm working? I'm on Windows. I've tried the -i option in ghci and ghc, but ghci and ghc don't see the SOE code. I tried many ways of specifying the directory to -i: with quotes, without quotes, relative path, absolute path. ghc happily accepts every form I give it! But then fails to find SOE. I would like either to get the -i form working, or even better have ghc read an environment variable so it happens automatically every time it starts. But back to the gist of my question last night: I am aware that most examples of recursion presented in the books so far do their processing "as the recursion unwinds." In other words: length :: [a] -> Int length [] = 0 length (x:xs) = 1 + length xs This function goes deeper and deeper into the recursion before doing any calculation, then does all the sums "on the way back out." Being an imperative programmer, I keep trying to write loops that accumulate "on the way down", like this: length' :: Int -> [a] -> Int length' s [] = s length' s (x:xs) = length' (s+1) xs length :: [a] -> Int length xs = length' 0 xs I suppose both forms are valid, but the first form seems to be most natural in most situations I've encountered in the exercises. I'm working with "Real World Haskell", "Haskell School of Expression," and "Yet Another Haskell Tutorial." My strategy is to work each book's early chapters before going further in any of the books, so I get multiple "takes" on the material. Thanks, Mike

On Thu, Mar 26, 2009 at 03:23:01PM -0700, Michael Mossey wrote:
But back to the gist of my question last night: I am aware that most examples of recursion presented in the books so far do their processing "as the recursion unwinds." In other words:
length :: [a] -> Int length [] = 0 length (x:xs) = 1 + length xs
This function goes deeper and deeper into the recursion before doing any calculation, then does all the sums "on the way back out."
Right, this is equivalent to length = foldr (+) 0 and results in expressions like (1 + (1 + (1 + (1 + ...)))), which isn't good in this particular case, since none of the additions can be performed until the very end of the list is reached, and all the sums are indeed done "on the way back out". There are some cases, however (such as when the result is some data structure that can be computed lazily, like another list) when this is exactly what you want.
Being an imperative programmer, I keep trying to write loops that accumulate "on the way down", like this:
length' :: Int -> [a] -> Int length' s [] = s length' s (x:xs) = length' (s+1) xs
length :: [a] -> Int length xs = length' 0 xs
And this is equivalent to length = foldl (+) 0 and results in expressions like (((((0 + 1) + 1) + 1) + 1) + ... ). This looks better at first glance, since the sums can start accumulating as you go. However, since Haskell is lazy, this particular version is no better, because the sums won't be evaluated until the result is needed anyway: instead of accumulating a number, you end up accumulating a giant thunk (unevaluated expression) which is only evaluated when its result is finally needed, after the call to length has already finished! So as long as you don't call length on really long lists, you might as well use your first version---if you're going to blow the stack on long lists anyway, you might as well do it in a more natural style. =) But read on... What we'd like is some way to force the accumulator to be evaluated as we recurse down the list---and this is exactly what the foldl' function (from Data.List) does, by introducing a bit of strictness. So the best way to write length is actually length = foldl' (+) 0. Whenever you see this 'accumulator' pattern over lists---some recursive function which recurses over a list while accumulating some small summary value---think foldl'.
I suppose both forms are valid, but the first form seems to be most natural in most situations I've encountered in the exercises.
The first is indeed more natural. Generally speaking, if you find yourself using accumulating parameters, there's probably a simpler way to do it, or some library function that already does exactly what you want to do. But it takes experience to learn and recognize such situations. -Brent
participants (4)
-
7stud
-
Brent Yorgey
-
Daniel Fischer
-
Michael Mossey