[Haskell-cafe] Trying to return a map from State monad

aditya siram aditya.siram at gmail.com
Thu May 19 22:57:59 CEST 2011


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 <nowgate at yahoo.com> wrote:

> 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 <nowgate at yahoo.com>* wrote:
>
>
> From: michael rice <nowgate at yahoo.com>
>
> Subject: Re: [Haskell-cafe] Trying to return a map from State monad
> To: "Thedward Blevins" <thedward at barsoom.net>
>
> Cc: haskell-cafe at 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 <thedward at barsoom.net>* wrote:
>
>
> From: Thedward Blevins <thedward at barsoom.net>
> Subject: Re: [Haskell-cafe] Trying to return a map from State monad
> To: "michael rice" <nowgate at yahoo.com>
> Cc: haskell-cafe at haskell.org
> Date: Thursday, May 19, 2011, 12:22 PM
>
> On Thu, May 19, 2011 at 11:03, michael rice <nowgate at yahoo.com> 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 at haskell.org <http://mc/compose?to=Haskell-Cafe@haskell.org>
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110519/2737d4ba/attachment.htm>


More information about the Haskell-Cafe mailing list