
Hi, studying IO with files, i got this tutorial program. By the way, i discover the Data.Map module. Several questions then come to my mind : q1: why, in mapM_, make (sort (keys grades)) ? keys is already sorted, isn't it? q2: why, in mapM_, have grades twice (in draw then keys). I wonder if writing only draw grades, one could then extract the s and g parts in the draw function (via keys and elems). From this, i have problems with the type of grades; which is it? The insert function, using insertWith should give Map k a, but foldr seems to change this (couldn't match expected type [Map k a] against inferred type Map [String] a1 on the mapM_ line . q3: To solve the types problem, I tried to debug : i can get the types for s, marks and avg but for g, it says not in scope. How can i get this information ? q4: I also tried to type the parameter in draw (draw (x::Map k a) = ...) but i got an error : Illegal signature in pattern use -XScopedTypeVariables to permit it Since this parameter is visibly not set by default in ghci, is it a good idea to set it ? Thanks and happy new year. Didier import Data.Char http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Char import Data.Maybe http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Maybe import Data.List import Data.Map hiding (map http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map) import Text.Printf main = do src <- readFile http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:readFi... "grades" let pairs = map http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map (split.words http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:words) (lines http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:lines src) let grades = foldr http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:foldr insert empty pairs mapM_ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:mapM_ (draw grades) (sort (keys grades)) where insert (s, g) = insertWith (++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.) s [g] split [name,mark] = (name, read http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:read mark) draw g s = printf "%s\t%s\tAverage: %f\n" s (show http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:show marks) avg where marks = findWithDefault (error http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:error "No such student") s g avg = sum http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:sum marks / fromIntegral http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fromIn... (length http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:length marks) :: Double http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Double

Am Donnerstag 31 Dezember 2009 12:53:05 schrieb legajid:
Hi, studying IO with files, i got this tutorial program. By the way, i discover the Data.Map module. Several questions then come to my mind : q1: why, in mapM_, make (sort (keys grades)) ? keys is already sorted, isn't it?
It is. That is also specified in the documentation, so it's superfluous. It may be a leftover from earlier versions using a data structure which doesn't guarantee to return the keys in ascending order.
q2: why, in mapM_, have grades twice (in draw then keys).
draw takes two arguments, a Map in which to look up the marks and a key to look up, the name of the student. The list of keys over which we want to mapM_ is the list of keys in the Map, (keys grades). The function we want to mapM_ is (look up marks of student in the Map grades and then output marks and average), that is (draw grades).
I wonder if writing only draw grades, one could then extract the s and g parts in the draw function (via keys and elems). From this, i have problems with the type of grades; which is it? The insert function, using insertWith should give Map k a, but foldr seems to change this (couldn't match expected type [Map k a] against inferred type Map [String] a1 on the mapM_ line .
? I don't understand what you tried to do there. You can write a function draw1 which takes only a Map as argument so that draw1 grades is the same as mapM_ (draw grades) (keys grades)
q3: To solve the types problem, I tried to debug : i can get the types for s, marks and avg but for g, it says not in scope. How can i get this information ?
g is a parameter of draw, so there is no entity g defined outside the definition of draw. To find the type of g, ask ghci: *Grades> :t draw draw :: (PrintfArg k, PrintfType t, Ord k) => Map k [Double] -> k -> t , since g is the first argument of draw, its type is the type to the left of the first (top level) '->', namely Map k [Double] (I have here ignored the type class constraints on k).
q4: I also tried to type the parameter in draw (draw (x::Map k a) = ...) but i got an error : Illegal signature in pattern use -XScopedTypeVariables to permit it Since this parameter is visibly not set by default in ghci, is it a good idea to set it ?
If you need it. Here, you can solve the problem with a type signature on draw, e.g. draw :: Map String [Double] -> String -> IO ()
Thanks and happy new year.
A vous aussi.
Didier
import Data.Char <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Char
import Data.Maybe <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Mayb e> import Data.List import Data.Map hiding (map http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map ) import Text.Printf
main = do src <- readFile <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:read File> "grades" let pairs = map http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map (split.words <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:word s>) (lines <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:line s> src) let grades = foldr <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fold r> insert empty pairs mapM_ <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:mapM _> (draw grades) (sort (keys grades)) where insert (s, g) = insertWith (++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.) s [g] split [name,mark] = (name, read <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:read
mark)
marks) avg where marks = findWithDefault (error <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:erro r> "No such student") s g avg = sum http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:sum marks / fromIntegral <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:from Integral> (length <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:leng
draw g s = printf "%s\t%s\tAverage: %f\n" s (show <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:show th> marks) :: Double <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Doub le>
participants (2)
-
Daniel Fischer
-
legajid