Can't access map value with key.

What am I doing wrong in the last line of main? If I comment out the last line of main, my program prints the map (mp) that is created. If I leave it in, the program fails. The last line should print the list ["I"]. Michael ================================================ import Control.Monad.Stateimport Data.Map type Prefix = (String,String)type GeneratorState = State ((Map Prefix [String]),Prefix,[String]) non_word = "\n" f key new old = new ++ old buildMap :: GeneratorState (Map Prefix [String])buildMap = do (mp,(pfx1,pfx2),words) <- get if (Prelude.null words) then {- No more words. Return final map (adding non_word for prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else do {- Add word to map at prefix & continue. -} put (insertWithKey' f (pfx1,pfx2) [head words] mp, (pfx2,(head words)), tail words) buildMap {-*Main> execState buildMap (singleton ("\n","\n") [], ("\n","\n"), ["I","am","lost."])(fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])],("am","lost."),[])*Main> -} nwords = 1 main = do contents <- getContents let mp = execState buildMap (singleton (non_word,non_word) [], (non_word,non_word), words contents) putStrLn $ show mp putStrLn $ show (mp ! (non_word,non_word)) ============================================== [michael@hostname ~]$ ghc --make markov4.hs[1 of 1] Compiling Main ( markov4.hs, markov4.o )Linking markov4 ...[michael@hostname ~]$ echo "I am lost." | ./markov4(fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])],("am","lost."),[])[michael@hostname ~]$ ghc --make markov4.hs[1 of 1] Compiling Main ( markov4.hs, markov4.o ) markov4.hs:35:27: Couldn't match expected type `Map k a' against inferred type `(Map Prefix [String], Prefix, [String])' In the first argument of `(!)', namely `mp' In the first argument of `show', namely `(mp ! (non_word, non_word))' In the second argument of `($)', namely `show (mp ! (non_word, non_word))'[michael@hostname ~]$

On Fri, 2011-05-20 at 19:04 -0700, michael rice wrote:
markov4.hs:35:27: Couldn't match expected type `Map k a' against inferred type `(Map Prefix [String], Prefix, [String])'
ghc seems to believe `mp' here is not just a map, but the entire state (which is what execState is meant to give you).
type GeneratorState = State ((Map Prefix [String]),Prefix,[String])
The state is a triple, so you need to match to get the real map out:
let (themap,_,_) = mp putStrLn $ show $ themap ! (non_word,non_word)

That works, but I don't understand how I can print the map mp on one line but then when I try to extract a value out of it it's no longer a map but a triple. How can mp be a map on one line but not on another?
Michael
=============
[1 of 1] Compiling Main ( markov4.hs, markov4.o )Linking markov4 ...[michael@hostname ~]$ echo "I am lost." | ./markov4(fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])],("am","lost."),[])["I"][michael@hostname ~]$ ghciGHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for helpLoading package ghc-prim ... linking ... done.Loading package integer-gmp ... linking ... done.Loading package base ... linking ... done.Loading package ffi-1.0 ... linking ... done.Prelude> :m + Data.MapPrelude Data.Map> let mp = fromList [(1,'a'),(2,'b'),(3,'c')]Loading package array-0.3.0.1 ... linking ... done.Loading package containers-0.3.0.0 ... linking ... done.Prelude Data.Map> :t mpmp :: Map Integer CharPrelude Data.Map> mpfromList [(1,'a'),(2,'b'),(3,'c')]Prelude Data.Map> mp ! 2'b'Prelude Data.Map>
--- On Fri, 5/20/11, Arlen Cuss
markov4.hs:35:27: Couldn't match expected type `Map k a' against inferred type `(Map Prefix [String], Prefix, [String])'
ghc seems to believe `mp' here is not just a map, but the entire state (which is what execState is meant to give you).
type GeneratorState = State ((Map Prefix [String]),Prefix,[String])
The state is a triple, so you need to match to get the real map out:
let (themap,_,_) = mp putStrLn $ show $ themap ! (non_word,non_word)

On Sat, 2011-05-21 at 04:56 -0700, michael rice wrote:
(fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])],("am","lost."),[])
Or splitting that out: (fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])], ("am","lost."), []) Note that it's a triple, not one map. You're printing the triple mp, the first item of which is a map. A

Duh...
Thanks, Arlen.
Michael
--- On Sat, 5/21/11, Arlen Cuss
(fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])],("am","lost."),[])
Or splitting that out: (fromList [(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."])], ("am","lost."), []) Note that it's a triple, not one map. You're printing the triple mp, the first item of which is a map. A
participants (2)
-
Arlen Cuss
-
michael rice