[Haskell] ANNOUNCE: generator 0.5.1

Yair Chuchem yairchu at gmail.com
Wed Jul 15 09:33:21 EDT 2009


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.

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20090715/dfca1bc7/attachment-0001.html


More information about the Haskell mailing list