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.State
import 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 ~]$