[Haskell-beginners] Problem with Data.Map and IO...

Michael Xavier nemesisdesign at gmail.com
Wed May 11 20:41:46 CEST 2011


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 <manfred.lotz at arcor.de>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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Michael Xavier
http://www.michaelxavier.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110511/89192a38/attachment-0001.htm>


More information about the Beginners mailing list