
Hi there, I've got a problem creating a map. I have a list of dataset names and adding those dataset names into a map works fine like this: <----------------------------snip--------------------------------> module Main where import Data.List import qualified Data.Map as M insertRec :: M.Map String String -> String -> M.Map String String insertRec m e = let f = M.lookup e m in if f == Nothing then M.insert e "bla" m else m createMap :: [String] -> M.Map String String createMap lst = let m = M.empty in foldl' insertRec m lst main :: IO () main = do let xmlfiles = [ "a.xml","f.xml"] let ht = createMap xmlfiles print ht <----------------------------snap--------------------------------> However, actually I want to parse the xml files and adding content into the map. For this I have a function getXmlContent :: FilePath -> IO (String,String) and would like to do something like this: <----------------------------snip--------------------------------> insertRec m e = do c <- getXmlContent e let k = fst c let v = snd c M.insert k v m <----------------------------snap--------------------------------> Unfortunately, this doesn't work because of IO. I have no glue how to get this done. Any help appreciated. -- Thanks, Manfred

I believe let when you're in do notation is for pure functions. Since c is
IO (String String), I think what you might try is:
c <- getXmlContent e
k <- fst c
v <- snd c
Or even better, use pattern matching:
(k, v) <- getXmlContent e
Someone please step in if I'm misrepresenting how it's done.
On Wed, May 11, 2011 at 11:05 AM, Manfred Lotz
Hi there, I've got a problem creating a map.
I have a list of dataset names and adding those dataset names into a map works fine like this:
<----------------------------snip--------------------------------> module Main where
import Data.List import qualified Data.Map as M
insertRec :: M.Map String String -> String -> M.Map String String insertRec m e = let f = M.lookup e m in if f == Nothing then M.insert e "bla" m else m
createMap :: [String] -> M.Map String String createMap lst = let m = M.empty in foldl' insertRec m lst
main :: IO () main = do let xmlfiles = [ "a.xml","f.xml"] let ht = createMap xmlfiles print ht <----------------------------snap-------------------------------->
However, actually I want to parse the xml files and adding content into the map.
For this I have a function getXmlContent :: FilePath -> IO (String,String)
and would like to do something like this:
<----------------------------snip--------------------------------> insertRec m e = do c <- getXmlContent e let k = fst c let v = snd c M.insert k v m <----------------------------snap-------------------------------->
Unfortunately, this doesn't work because of IO. I have no glue how to get this done.
Any help appreciated.
-- Thanks, Manfred
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Michael Xavier http://www.michaelxavier.net

You want the Map to map from filenames to their contents?
Basically you need mapM or foldM, depending in where you want to use
getXmlContent. In the below code I used mapM to read the files into a
list of pairs, and fold over it (I changed insertRec to take a pair).
--
module Main where
import Data.List
import qualified Data.Map as M
import Control.Monad (mapM)
insertRec :: M.Map String String -> (String, String) -> M.Map String String
insertRec m (key, value) =
if M.lookup key m == Nothing
then M.insert key value m
else m
insertRec2 m (key, value) =
M.insertWith const key value m
createMap :: [(String, String)] -> M.Map String String
createMap lst = foldl' insertRec M.empty lst
getXmlContent :: FilePath -> IO (String,String)
getXmlContent filename = do
contents <- readFile filename
return (filename, contents)
main :: IO ()
main = do
xmlfiles <- mapM getXmlContent ["a.xml","f.xml", "a.xml"]
let ht = createMap xmlfiles
print ht
--
You could also read the files in insertRec instead of in main -- that
would make insertRec return an "IO (M.Map String String)" instead of
just "M.Map String String". And then you have to use foldM in
createMap to use it, because the folding function is monadic now.
On 5/11/11, Michael Xavier
I believe let when you're in do notation is for pure functions. Since c is IO (String String), I think what you might try is:
c <- getXmlContent e k <- fst c v <- snd c
Or even better, use pattern matching:
(k, v) <- getXmlContent e
Someone please step in if I'm misrepresenting how it's done.
On Wed, May 11, 2011 at 11:05 AM, Manfred Lotz
wrote: Hi there, I've got a problem creating a map.
I have a list of dataset names and adding those dataset names into a map works fine like this:
<----------------------------snip--------------------------------> module Main where
import Data.List import qualified Data.Map as M
insertRec :: M.Map String String -> String -> M.Map String String insertRec m e = let f = M.lookup e m in if f == Nothing then M.insert e "bla" m else m
createMap :: [String] -> M.Map String String createMap lst = let m = M.empty in foldl' insertRec m lst
main :: IO () main = do let xmlfiles = [ "a.xml","f.xml"] let ht = createMap xmlfiles print ht <----------------------------snap-------------------------------->
However, actually I want to parse the xml files and adding content into the map.
For this I have a function getXmlContent :: FilePath -> IO (String,String)
and would like to do something like this:
<----------------------------snip--------------------------------> insertRec m e = do c <- getXmlContent e let k = fst c let v = snd c M.insert k v m <----------------------------snap-------------------------------->
Unfortunately, this doesn't work because of IO. I have no glue how to get this done.
Any help appreciated.
-- Thanks, Manfred
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Michael Xavier http://www.michaelxavier.net
-- Markus Läll

Hi,
Thanks to both of you.
On Thu, 12 May 2011 03:19:24 +0300
Markus Läll
You want the Map to map from filenames to their contents?
Basically you need mapM or foldM, depending in where you want to use getXmlContent. In the below code I used mapM to read the files into a list of pairs, and fold over it (I changed insertRec to take a pair).
Actually I had tried foldM because I thought this has to be the way. But when I changed createMap accordingly I didn't think about changing the signature and then I didn't understand the compiler's error message. foldM works fine now. Now I have another problem which should be a new thread. -- Manfred
participants (3)
-
Manfred Lotz
-
Markus Läll
-
Michael Xavier