
Hi I just started on haskell , i am using the yet another haskell tutorial by Hal Daume I wrote the following program and it dint compile. what's wrong with it module Main where import IO main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn "Sum is " ++ show(sum) makeList = do putStrLn "enter a num" num <- getLine let nbr = read num if nbr == 0 then do return [] else do all <- makeList return (nbr : all) ---------------------------------------------- the error i get is Chasing modules from: Sum.hs Compiling Main ( Sum.hs, Sum.o ) Sum.hs:6: Couldn't match `[a]' against `IO ()' Expected type: [a] Inferred type: IO () In the application `putStrLn "Sum is "' In the first argument of `(++)', namely `putStrLn "Sum is "' Sum.hs:9: Couldn't match `[b]' against `IO [a]' Expected type: [b] Inferred type: IO [a] In the third argument of `foldr', namely `testList' In the definition of `sum': sum = foldr (+) 0 testList ----------------------------- Thanks, Abhijit Ray

On 11/4/05, Abhijit Ray
I wrote the following program and it dint compile. what's wrong with it
module Main where
import IO
main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn "Sum is " ++ show(sum)
Write either testList <- makeList or sum <- liftM (foldr (+) 0) testList You probably want the former form. BTW, there is a sum function in Haskell prelude. Best regards Tomasz

On 04/11/05, Abhijit Ray
Hi I just started on haskell , i am using the yet another haskell tutorial by Hal Daume
I wrote the following program and it dint compile. what's wrong with it
module Main where
import IO
main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn "Sum is " ++ show(sum)
makeList = do putStrLn "enter a num" num <- getLine let nbr = read num if nbr == 0 then do return [] else do all <- makeList return (nbr : all) ---------------------------------------------- the error i get is
Chasing modules from: Sum.hs Compiling Main ( Sum.hs, Sum.o )
Sum.hs:6: Couldn't match `[a]' against `IO ()' Expected type: [a] Inferred type: IO () In the application `putStrLn "Sum is "' In the first argument of `(++)', namely `putStrLn "Sum is "'
Sum.hs:9: Couldn't match `[b]' against `IO [a]' Expected type: [b] Inferred type: IO [a] In the third argument of `foldr', namely `testList' In the definition of `sum': sum = foldr (+) 0 testList -----------------------------
Thanks, Abhijit Ray
Hello, The first error is related to the way in which the following line parses:
putStrLn "Sum is " ++ show(sum)
which is like: (putStrLn "Sum is") ++ (show sum) It's complaining that you're passing an IO action to (++). It's an easy fix, add some parens, or a well-placed ($): putStrLn $ "Sum is" ++ show sum The second problem arises due to not running the IO action you wanted to:
main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn $ "Sum is " ++ show sum What is the type of testList? Well, it must be the same as makeList -- what is makeList's type? The definition of makeList is in the form of a do-block which carries out an IO computation producing a list of numbers, so it's (Num a) => IO [a]. Note that this is not a list, so it's unsuitable for passing to foldr.
What do we do? We run the IO action using "<-":
main = do hSetBuffering stdin LineBuffering testList <- makeList let sum = foldr (+) 0 testList putStrLn $ "Sum is " ++ show sum This will cause the running of main to *run* the IO action makeList, getting the result into the list testList, which now has type (Num a) => [a] (here a is going to be defaulted to Integer, since nothing says otherwise, and one needs to pick something to be able to read).
Hope this helps, and good luck with Haskell :) - Cale

Thanks Tomasz and Cale, it worked now !
On 11/4/05, Cale Gibbard
On 04/11/05, Abhijit Ray
wrote: Hi I just started on haskell , i am using the yet another haskell tutorial by Hal Daume
I wrote the following program and it dint compile. what's wrong with it
module Main where
import IO
main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn "Sum is " ++ show(sum)
makeList = do putStrLn "enter a num" num <- getLine let nbr = read num if nbr == 0 then do return [] else do all <- makeList return (nbr : all) ---------------------------------------------- the error i get is
Chasing modules from: Sum.hs Compiling Main ( Sum.hs, Sum.o )
Sum.hs:6: Couldn't match `[a]' against `IO ()' Expected type: [a] Inferred type: IO () In the application `putStrLn "Sum is "' In the first argument of `(++)', namely `putStrLn "Sum is "'
Sum.hs:9: Couldn't match `[b]' against `IO [a]' Expected type: [b] Inferred type: IO [a] In the third argument of `foldr', namely `testList' In the definition of `sum': sum = foldr (+) 0 testList -----------------------------
Thanks, Abhijit Ray
Hello,
The first error is related to the way in which the following line parses:
putStrLn "Sum is " ++ show(sum)
which is like: (putStrLn "Sum is") ++ (show sum) It's complaining that you're passing an IO action to (++). It's an easy fix, add some parens, or a well-placed ($): putStrLn $ "Sum is" ++ show sum
The second problem arises due to not running the IO action you wanted to:
main = do hSetBuffering stdin LineBuffering let testList = makeList let sum = foldr (+) 0 testList putStrLn $ "Sum is " ++ show sum What is the type of testList? Well, it must be the same as makeList -- what is makeList's type? The definition of makeList is in the form of a do-block which carries out an IO computation producing a list of numbers, so it's (Num a) => IO [a]. Note that this is not a list, so it's unsuitable for passing to foldr.
What do we do? We run the IO action using "<-":
main = do hSetBuffering stdin LineBuffering testList <- makeList let sum = foldr (+) 0 testList putStrLn $ "Sum is " ++ show sum This will cause the running of main to *run* the IO action makeList, getting the result into the list testList, which now has type (Num a) => [a] (here a is going to be defaulted to Integer, since nothing says otherwise, and one needs to pick something to be able to read).
Hope this helps, and good luck with Haskell :) - Cale
participants (3)
-
Abhijit Ray
-
Cale Gibbard
-
Tomasz Zielonka