
In the last line of this program, I get the following error message (from ghci)... Couldn't match expected type `Int' against inferred type `Char' Expected type: [Int] Inferred type: String In the first argument of `median', namely `lst' In the expression: median lst Failed, modules loaded: none. Here's the program... module Main where import IO lessThan :: Int -> [Int] -> [Int] lessThan x lst = filter (< x) lst greaterThan :: Int -> [Int] -> [Int] greaterThan x lst = filter (> x) lst numLessThan :: Int -> [Int] -> Int numLessThan x lst = length (lessThan x lst) numGreaterThan :: Int -> [Int] -> Int numGreaterThan x lst = length (greaterThan x lst) numLessGreater :: Int -> [Int] -> (Int, Int) numLessGreater x lst = (numLessThan x lst, numGreaterThan x lst) isMedian :: (Int, Int) -> Bool isMedian (x, y) = x == y medians :: [Int] -> [Int] medians lst = [x | x <- lst, isMedian (numLessGreater x lst)] median :: [Int] -> Int median lst = case medians lst of -- All the values in the result are the same, we just pick the first one x:xs -> x main = do putStr "Enter a list: " lst <- getLine median lst I'm sure this is because Haskell isn't automatically changing a String to a List of numbers. But how can I do this? Thanks.

Hi Barry, You can use read: ... lst <- getline median (read lst::[Int]) ... You will have to enter your list like this at the prompt:
[1,2,3,4]
read transforms Strings into some other type (usually specified by a type annotation). read :: Read a => String -> a HTH Chris. On Wed, 20 Aug 2008, Barry Burd wrote:
In the last line of this program, I get the following error message (from ghci)...
Couldn't match expected type `Int' against inferred type `Char' Expected type: [Int] Inferred type: String In the first argument of `median', namely `lst' In the expression: median lst Failed, modules loaded: none.
Here's the program...
module Main where
import IO
lessThan :: Int -> [Int] -> [Int] lessThan x lst = filter (< x) lst
greaterThan :: Int -> [Int] -> [Int] greaterThan x lst = filter (> x) lst
numLessThan :: Int -> [Int] -> Int numLessThan x lst = length (lessThan x lst) numGreaterThan :: Int -> [Int] -> Int numGreaterThan x lst = length (greaterThan x lst)
numLessGreater :: Int -> [Int] -> (Int, Int) numLessGreater x lst = (numLessThan x lst, numGreaterThan x lst)
isMedian :: (Int, Int) -> Bool isMedian (x, y) = x == y
medians :: [Int] -> [Int] medians lst = [x | x <- lst, isMedian (numLessGreater x lst)]
median :: [Int] -> Int median lst = case medians lst of -- All the values in the result are the same, we just pick the first one x:xs -> x
main = do putStr "Enter a list: " lst <- getLine median lst
I'm sure this is because Haskell isn't automatically changing a String to a List of numbers. But how can I do this? Thanks.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Barry, Barry Burd wrote:
median :: [Int] -> Int median lst = case medians lst of -- All the values in the result are the same, we just pick the first one x:xs -> x
main = do putStr "Enter a list: " lst <- getLine median lst
I'm sure this is because Haskell isn't automatically changing a String to a List of numbers. But how can I do this?
Use the "read" function. Watch out, though - there is no error checking there. So if the user enters a string that does not have the right syntax for a Haskell list of integers, your program will halt with an error message. You have another problem - you used the "median" function as a step in a do block - but each step in a do block must have type "IO a" for some type a. Here's how you could write your main function: main = do putStr "Enter a list: " lst <- getLine print $ median $ read lst Regards, Yitz

Barry, On another note, you may want to avoid monads altogether for this. You can run this straight from ghci (replacing mainProg with main) mainProg :: [Int] -> Int mainProg arg = median lst and then call mainProg with your desired list of stings
mainProg [1,2,3,4]
Chris. On Wed, 20 Aug 2008, Yitzchak Gale wrote:
Hi Barry,
Barry Burd wrote:
median :: [Int] -> Int median lst = case medians lst of -- All the values in the result are the same, we just pick the first one x:xs -> x
main = do putStr "Enter a list: " lst <- getLine median lst
I'm sure this is because Haskell isn't automatically changing a String to a List of numbers. But how can I do this?
Use the "read" function. Watch out, though - there is no error checking there. So if the user enters a string that does not have the right syntax for a Haskell list of integers, your program will halt with an error message.
You have another problem - you used the "median" function as a step in a do block - but each step in a do block must have type "IO a" for some type a.
Here's how you could write your main function:
main = do putStr "Enter a list: " lst <- getLine print $ median $ read lst
Regards, Yitz _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Or, call median with your list of ints and forget about mainProg...:) Chris. On Wed, 20 Aug 2008, C.M.Brown wrote:
Barry,
On another note, you may want to avoid monads altogether for this. You can run this straight from ghci (replacing mainProg with main)
mainProg :: [Int] -> Int mainProg arg = median lst
and then call mainProg with your desired list of stings
mainProg [1,2,3,4]
Chris.
On Wed, 20 Aug 2008, Yitzchak Gale wrote:
Hi Barry,
Barry Burd wrote:
median :: [Int] -> Int median lst = case medians lst of -- All the values in the result are the same, we just pick the first one x:xs -> x
main = do putStr "Enter a list: " lst <- getLine median lst
I'm sure this is because Haskell isn't automatically changing a String to a List of numbers. But how can I do this?
Use the "read" function. Watch out, though - there is no error checking there. So if the user enters a string that does not have the right syntax for a Haskell list of integers, your program will halt with an error message.
You have another problem - you used the "median" function as a step in a do block - but each step in a do block must have type "IO a" for some type a.
Here's how you could write your main function:
main = do putStr "Enter a list: " lst <- getLine print $ median $ read lst
Regards, Yitz _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

2008/8/20 Yitzchak Gale
Here's how you could write your main function:
main = do putStr "Enter a list: " lst <- getLine print $ median $ read lst
Another possibility would be a space delimited number list, easier for your users to remember :
parseWordList :: (Read a) => String -> [a] parseWordList str = map read . unwords $ str
main = do putStrLn "Enter a list of integers : " line <- getLine print . median . parseWordList $ line
-- Jedaï

2008/8/21 Chaddaï Fouché
Another possibility would be a space delimited number list, easier for your users to remember :
parseWordList :: (Read a) => String -> [a] parseWordList str = map read . unwords $ str
Oups, that was wrong :
parseWordList :: (Read a) => String -> [a] parseWordList str = map read . words $ str
-- Jedaï

Chaddaï Fouché wrote:
Another possibility would be a space delimited number list, easier for your users to remember :
parseWordList :: (Read a) => String -> [a] parseWordList str = map read . words $ str
Even nicer, here is a function that will allow the user to enter a "list of numbers" in any reasonable format. If the input doesn't make sense as a "list of numbers", the empty list is returned: parseWordList :: (Read a) => String -> [a] parseWordList = unfoldr $ listToMaybe . concatMap reads . tails You'll need to import the Data.List and Data.Maybe libraries for this. Here is a snippet from a GHCi session that illustrates its use: Prelude Data.List Data.Maybe> parseWordList "The numbers are 34, 56, and 22." :: [Int] [34,56,22] Regards, Yitz
participants (4)
-
Barry Burd
-
C.M.Brown
-
Chaddaï Fouché
-
Yitzchak Gale