Trying to return a map from State monad

I'm not sure what's going on BELOW. Was working with mapAccumL earlier and decided to move over to State monad for more control. :m + Data.Map:m + Data.ListPrelude Data.List Data.Map> let f key new old = new ++ oldPrelude Data.List Data.Map> let moby2 = "Moby Dick is a great book. Moby Dick was a white whale."Prelude Data.List Data.Map> fst $ mapAccumL (\ (m,p) w -> ((insertWithKey' f p [w] m, (snd p, w)),"")) (singleton ("\n", "\n") [], ("\n","\n")) (words moby2)(fromList [(("\n","\n"),["Moby"]),(("\n","Moby"),["Dick"]),(("Dick","is"),["a"]),(("Dick","was"),["a"]),(("Moby","Dick"),["was","is"]),(("a","great"),["book."]),(("a","white"),["whale."]),(("book.","Moby"),["Dick"]),(("great","book."),["Moby"]),(("is","a"),["great"]),(("was","a"),["white"])],("white","whale.")) Michael BELOW=========================== import Control.Monad.Stateimport Data.Map type Prefix = (String,String)type GeneratorState = (Map Prefix [String],Prefix,[String]) non_word = "\n" f key new old = new ++ old buildMap :: GeneratorState (Map Prefix [String]) buildMap = do (mp,(pfx1,pfx2),all@(w1:words)) <- get if (Prelude.null all) then {- No more words. Return final map (adding non_word for prefix). -} return (insertWithKey' f (pfx1,pfx2) [non_word] mp) else {- Add word to map at prefix. Continue. -} put (insertWithKey' f (pfx1,pfx2) [w1] mp, (pfx2,w1), words) buildMap ========================== Prelude> :l markov3.hs[1 of 1] Compiling Main ( markov3.hs, interpreted ) markov3.hs:11:12: `GeneratorState' is applied to too many type arguments In the type signature for `buildMap': buildMap :: GeneratorState (Map Prefix [String])Failed, modules loaded: none.

On Thu, May 19, 2011 at 11:03, michael rice
type GeneratorState = (Map Prefix [String],Prefix,[String])
buildMap :: GeneratorState (Map Prefix [String])
You are trying to use a type alias (GeneratorState) as a type constructor. There may be other problems, but that leaps out.

Ok, I see I left out the "State" word.
Should be:type GeneratorState = State (Map Prefix [String],Prefix,[String])
Thanks,
Michael
--- On Thu, 5/19/11, Thedward Blevins
type GeneratorState = (Map Prefix [String],Prefix,[String])
buildMap :: GeneratorState (Map Prefix [String])
You are trying to use a type alias (GeneratorState) as a type constructor. There may be other problems, but that leaps out.

OK. Again, not sure what going on here. Pattern looks OK to me.
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),all@(w1:words)) <- get if (Prelude.null all) 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) [w1] mp, (pfx2,w1), words) buildMap
=============================
*Main> :r[1 of 1] Compiling Main ( markov3.hs, interpreted )Ok, modules loaded: Main.*Main> fst $ runState buildMap (singleton ("\n","\n") [], ("\n","\n"), ["I","am","lost."])fromList *** Exception: Pattern match failure in do expression at markov3.hs:13:14-44
--- On Thu, 5/19/11, michael rice
type GeneratorState = (Map Prefix [String],Prefix,[String])
buildMap :: GeneratorState (Map Prefix [String])
You are trying to use a type alias (GeneratorState) as a type constructor. There may be other problems, but that leaps out. -----Inline Attachment Follows----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The problem is that the "all@(w1:words)" pattern-match fails when "all" is
empty. The quick and dirty fix is:
import Control.Monad.State
import Data.Map
import Debug.Trace
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),all) <- get
if (Prelude.null all)
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 all] mp,
(pfx2,head all), tail all)
buildMap
*Main> fst $ runState buildMap (singleton ("\n","\n") [], ("\n","\n"),
["I","am","lost."])
fromList
[(("\n","\n"),["I"]),(("\n","I"),["am"]),(("I","am"),["lost."]),(("am","lost."),["\n"])]
A better one would be to write a helper function that correctly pattern
matched on the list.
-deech
On Thu, May 19, 2011 at 3:30 PM, michael rice
OK. Again, not sure what going on here. Pattern looks OK to me.
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),all@(w1:words)) <- get if (Prelude.null all) 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) [w1] mp, (pfx2,w1), words) buildMap
=============================
*Main> :r [1 of 1] Compiling Main ( markov3.hs, interpreted ) Ok, modules loaded: Main. *Main> fst $ runState buildMap (singleton ("\n","\n") [], ("\n","\n"), ["I","am","lost."]) fromList *** Exception: Pattern match failure in do expression at markov3.hs:13:14-44
--- On *Thu, 5/19/11, michael rice
* wrote: From: michael rice
Subject: Re: [Haskell-cafe] Trying to return a map from State monad To: "Thedward Blevins"
Cc: haskell-cafe@haskell.org Date: Thursday, May 19, 2011, 12:41 PM
Ok, I see I left out the "State" word.
Should be: type GeneratorState = State (Map Prefix [String],Prefix,[String])
Thanks,
Michael
--- On *Thu, 5/19/11, Thedward Blevins
* wrote: From: Thedward Blevins
Subject: Re: [Haskell-cafe] Trying to return a map from State monad To: "michael rice" Cc: haskell-cafe@haskell.org Date: Thursday, May 19, 2011, 12:22 PM On Thu, May 19, 2011 at 11:03, michael rice
wrote: type GeneratorState = (Map Prefix [String],Prefix,[String])
buildMap :: GeneratorState (Map Prefix [String])
You are trying to use a type alias (GeneratorState) as a type constructor.
There may be other problems, but that leaps out.
-----Inline Attachment Follows-----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mc/compose?to=Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

A laugh a minute. I though of that and tried it but got the same response (forgetting to :r my source) before rerunning. Time for a break.
Thanks!
Michael
--- On Thu, 5/19/11, aditya siram
type GeneratorState = (Map Prefix [String],Prefix,[String])
buildMap :: GeneratorState (Map Prefix [String])
You are trying to use a type alias (GeneratorState) as a type constructor. There may be other problems, but that leaps out. -----Inline Attachment Follows----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
aditya siram
-
michael rice
-
Thedward Blevins