[Haskell] ANNOUNCE: generator 0.5.1

Yair Chuchem yairchu at gmail.com
Wed Jul 15 18:31:03 EDT 2009


I did not know about ChoiceT.

It does offer the same basic functionality:
runChoiceT :: (Monad m) => ChoiceT m a -> m (Maybe (a,ChoiceT m a))
runChoiceT is equivalent to my runListT, and for the "Hamurabi"  
example ChoiceT would work just as well as ListT.

An interesting thing is that I arrived to ListT from a totally  
different perpective:
A monadic list as an alternative to Lazy IO and Iteratee (I'm not  
claiming this provides everything Iteratee does).
That's what brought me to implement scanl, takeWhile, and other list  
operations for ListT.

Other related monads:

Sebastian Fisher's "Reinventing Haskell Backtracking" (http://www-ps.informatik.uni-kiel.de/~sebf/pub/atps09.html 
)
seems to be similar (I think).
and Dan Piponi's PList monad (http://blog.sigfpe.com/2009/07/monad-for-combinatorial-search-with.html 
)
offers a similar functionality to my bestFirstSeachSortedChildrenOn  
function
(http://hackage.haskell.org/packages/archive/generator/0.5.1/doc/html/Data-List-Tree.html#v%3AbestFirstSearchSortedChildrenOn 
).
pythagorianTriplets =
   catMaybes .
   fmap fst .
   bestFirstSearchSortedChildrenOn snd .
   generate $ do
     x <- lift [1..]
     yield (Nothing, x)
     y <- lift [1..]
     yield (Nothing, x + y)
     z <- lift [1..]
     yield (Nothing, x + y + z)
     lift . guard $ x^2 + y^2 == z^2
     yield (Just (x, y, z), 0)

 > print $ take 10 pythagorianTriplets
[(3,4,5),(4,3,5),(6,8,10),(8,6,10),(5,12,13),(12,5,13),(9,12,15), 
(12,9,15),(15,8,17),(8,15,17)]
cheers,
Yair

On Jul 16, 2009, at 12:24 AM, Sjoerd Visscher wrote:

> 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/5ea149b1/attachment-0001.html


More information about the Haskell mailing list