[Haskell-beginners] Some confusion still with a YAHT example

Daniel Fischer daniel.is.fischer at web.de
Wed Jan 7 21:35:39 EST 2009


Am Donnerstag, 8. Januar 2009 01:31 schrieb David Schonberger:
> Hello all. This is my first post and I'm essentially a rank beginner with
> Haskell, having used it briefly some 7 years ago. Glad to be back but
> struggling with syntax and understanding error messages.
>
> This post actually ties to a prior post,
> http://www.haskell.org/pipermail/beginners/2008-December/000583.html
>
> My troubles are with exercise 3.10, p45 of from HDIII's "Yet Another
> Haskell Tutorial" (YAHT). The exercise states:
>
> Write a program that will repeatedly ask the user for numbers until she
> types in zero, at which point it will tell her the sum of all the numbers,
> the product of all the numbers, and, for each number, its factorial. For
> instance, a session might look like:
>
> Note that the sample session accompanying the exercise suggests a session
> such as:
>
> Give me a number (or 0 to stop):
> 5
> Give me a number (or 0 to stop):
> 8
> Give me a number (or 0 to stop):
> 2
> Give me a number (or 0 to stop):
> 0
> The sum is 15
> The product is 80
> 5 factorial is 120
> 8 factorial is 40320
> 2 factorial is 2
>
> The following code handles the sum and products pieces--I built the module
> incrementally--but fails on the factorial part. In fact my current code, if
> it worked, would only output something like:
>
> The sum is 15
> The product is 80
> 120
> 40320
> 2
>
> But I'm not even getting that much. Here's the code:
>
> --begin code
>
> module AskForNumbers whereimport IO askForNums = do putStrLn "Enter a pos
> int or 0 to end: " numStr <- getLine let num = read numStr if num == 0 
> then return []  else do   rest <- askForNums   return (num:rest)
>
> listFactorial l =  if length l == 0  then return 1  else do   fact (head l)
>   listFactorial (tail l)
>
> fact n =  if n == 0   then return 1  else return foldr (*) 1 [1..n]  f = do
> nums <- askForNums putStr ("Sum is " ++ (show (foldr (+) 0 nums)) ++ "\n")
> putStr ("Product is " ++ (show (foldr (*) 1 nums)) ++ "\n") listFactorial
> nums
>
> --end code
>
> Here is the error msg I get when I load into WinHugs (Sept 2006 version):
>
> ERROR file:.\AskForNumbers.hs:22 - Ambiguous type signature in inferred
> type *** ambiguous type : (Num a, Num [a], Monad ((->) [b]), Num c, Num (b
> -> [a] -> [a]), Enum a, Monad ((->) (c -> c -> c))) => a -> [b] -> [a] ***
> assigned to : fact
>
> Ambiguous type assigned to fact. Ok. Not sure what to make of that or how
> to correct it. I though I was passing fact an Integer, since I think nums
> is a list of Integers, since the sum and product lines in f work ok.
>
> Help? Thanks.

Okay, that's a nice one :) Don't be disappointed by the rather prosaic reason 
for it. 
First, if you don't already know what ambiguous type means: in the context 
"(Num a, ..., Monad ((->) (c -> c -> c)))" there appears a type variable, c, 
which doesn't appear on the right hand side a -> [b] -> [a].
I will not explain how that monstrous type arises, though it is a nice 
exercise in type inferring.

module AskForNumbers where

import IO

askForNums = do
    putStrLn "Enter a pos int or 0 to end: "
    numStr <- getLine
    let num = read numStr
    if num == 0 then return []
      else do
        rest <- askForNums
        return (num:rest)


listFactorial l = if length l == 0 then return 1
                    else do
                        fact (head l)
                        listFactorial (tail l)
^^^^
There are several things that can be improved here. 
First, don't use "if length l == 0". 
That has to traverse the whole list and if that's long (or even infinite), 
you're doing a lot of superfluous work. To check for an empty list, use 
"null", so "if null l then ...", that's far more efficient because null is 
defined as
null [] = True
null _ = False

Also, it would be better to define listFactorial by pattern matching:
listFactorial [] = ...
listFactorial (k:ks) = do
	fact k
	listFactorial ks

Next, why do you return 1 for an empty list?
Probably to match the type of the other branch, but that that isn't so well 
chosen either.
And since fact only returns something and does nothing else, listFactorial 
actually is "do something without any effects and then return 1", that isn't 
what you want. What you want is that for each k in the list it prints
k factorial is ...
That suggests that you either let fact do the output, so that fact would get 
the type 
Int(eger) -> IO ()
or let fact be a pure function calculating the factorial and have
listFactorial (k:ks) = do
	putStrLn (show k ++ " factorial is " ++ show (fact k))
	listFactorials ks

f = do
    nums <- askForNums
    putStr ("Sum is " ++ (show (foldr (+) 0 nums)) ++ "\n")
    putStr ("Product is " ++ (show (foldr (*) 1 nums)) ++ "\n")
    listFactorial nums

There are library functions "sum" and "product", you could use them.
Instead of 
putStr (some string ++ "\n")
you could use 
putStrLn (some string)
but all this is just a matter of personal taste.


Now comes the culprit:

fact n = if n == 0  
		then 
		    return 1 
		else 
		    return foldr (*) 1 [1 .. n]

The else-branch should be
return ( foldr (*) 1 [1 .. n] )
or
return $ foldr (*) 1 [1 .. n]

Without the parentheses or ($), it is parsed as
( ( (return foldr) (*) ) 1 ) [1 .. n], 
which leads to the interesting type of the error message.

If you're interested, I could explain how hugs infers that.

>
> David

HTH,
Daniel



More information about the Beginners mailing list