[Haskell] ANNOUNCE: generator 0.5.1
Sjoerd Visscher
sjoerd at w3future.com
Wed Jul 15 17:24:55 EDT 2009
This sounds similar to ChoiceT from the monadLib package. Did you know
ChoiceT?
greetings,
Sjoerd
On Jul 15, 2009, at 3:33 PM, Yair Chuchem wrote:
> A new "generator" package has been uploaded to Hackage.
>
> It implements an alternative list monad transformer, a list class,
> and related functions.
>
> The difference from mtl/transformers's ListT is that
> mtl is a monadic action that returns a list:
> newtype ListT m a = ListT { runListT :: m [a] }
> generator's is a monadic list:
> data ListItem l a = Nil | Cons { headL :: a, tailL :: l a }
> newtype ListT m a = ListT { runListT :: m (ListItem (ListT m) a) }
> A short example program which reads numbers from the user and
> interactively sums them up:
> import Control.Monad.ListT (ListT)
> import Data.List.Class (execute, joinM, repeat, scanl, takeWhile)
> import Prelude hiding (repeat, scanl, takeWhile)
>
> main =
> execute . joinM . fmap print .
> scanl (+) 0 .
> fmap (fst . head) .
> takeWhile (not . null) .
> fmap reads .
> joinM $ (repeat getLine :: ListT IO (IO String))
> I also wrote an example/blog-post about using ListT to add an undo
> option to the classic game of "hamurabi":
> http://mashebali.blogspot.com/2009/07/charlemagne-disraeli-and-jefferson.html
>
> Another interesting observation is that "ListT [] a" is a tree of
> "a"s.
> The module Data.List.Tree includes functions to prune and search
> such trees (dfs, bfs, bestFirstSearchOn, etc).
> This can be useful for modularizing code that uses the list monad
> for combinatoric search by decoupling tree creation from processing
> and pruning.
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
--
Sjoerd Visscher
sjoerd at w3future.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20090715/c68b3f2c/attachment.html
More information about the Haskell
mailing list