Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-22 Thread Sebastian Fischer


On Jun 19, 2009, at 7:12 PM, Sjoerd Visscher wrote:

I see you did performance tests. How does your current version  
compare to f.e. one based on DiffLists?


The current versions (0.4) of bfs and idfs based on FMList (0.5) use  
the same amount of memory and are about 10-15% slower than  
corresponding versions of breadth-first search and iterative deepening  
depth-first search based on CPS and DiffList when enumerating  
pythagorean triples without an upper bound (I didn't check other  
examples).


I wonder though, aren't you worried that updated versions of FMList  
might use the monoid laws to rewrite certains bits, and your code  
would break? Essentially you are using FMLists as a tree structure,  
which isn't possible when you abide by the monoid laws.


Manipulating w.r.t. monoid laws may change the order in which results  
are computed by bfs and idfs. However, I won't consider this breaking  
the code. The important property of bfs and idfs is that all results  
are eventually computed and I happily abstract from their order when  
enumerating results of non-deterministic computations. Other people  
may disagree though, so I should mention something about it in the docs.


If rewriting FMList w.r.t. monoid laws would break the completeness of  
the strategies I would be concerned. But currently I have the  
impression that parametricity ensures that I will always be able to  
convert an FMList into the (implicit) tree structures that I use for  
complete search.


I think you should be able to do the same thing in as many lines,  
using f.e. the ChoiceT type from MonadLib, where bfs and idfsBy are  
variations on runChoiceT.


I think so too. With a monad instance for a tree structure one can  
implement both strategies as well. However, the continuation-based  
implementation of monadic bind is more efficient when nested left  
associatively [1]. One could regain the asymptotic improvement of  
monadic bind by wrapping ChoiceT under ContT but that seems inelegant  
as it uses more monads than necessary.


By using a free representation of a pointed monoid one could use  
fmlists to generate the tree structure of a search space:


  data PMonoid a = Point a | Empty | Append (PMonoid a) (PMonoid a)

  instance Monoid PMonoid where
mempty  = Empty
mappend = Append

  treeSearch :: FMList a - PMonoid a
  treeSearch l = unFM l Point

Just like this monoid instance violates the monoid laws, the monad  
ChoiceT m violates corresponding laws of MonadPlus:


mzero `mplus` return 42
  = Choice NoAnswer (Answer 42)
 /= Answer 42
  = return 42

a `mplus` (b `mplus` c)
  = Choice a (Choice b c)
 /= Choice (Choice a b) c
  = (a `mplus` b) `mplus` c

So also w.r.t. laws there is no advantage in using a tree monad  
explicitly. Manipulating a non-deterministic computation w.r.t. these  
laws will change the order of computed results.


Mike Spivey gets by without breaking these laws by introducing an  
additional combinator 'wrap' to increase the depth of the search [2].  
However, this additional combinator prevents the use of (only)  
MonadPlus and whether all results of a non-deterministic computation  
are eventually enumerated depends on appropriate use of 'wrap'.


Cheers,
Sebastian


[1]: J. Voigtländer, Asymptotic Improvement of Computations over Free  
Monads

  http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf

[2]: Michael Spivey, Algebras for Combinatorial Search
  http://spivey.oriel.ox.ac.uk/mike/search-jfp.pdf

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)





PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sebastian Fischer


On Jun 18, 2009, at 9:57 AM, Sjoerd Visscher wrote:


This is my first package on Hackage, so any comments are welcome!


It is not only pleasingly elegant but also quite useful:

Your Monad and MonadPlus instances lead me to an interesting  
observation. Various strategies for non-deterministic search can be  
implemented using FMList by expressing failure and choice via a Monoid  
instance.


I have just finished a revision of a paper that explains how to factor  
two-continuation based backtracking (and other strategies) into a  
continuation monad transformer and a type class for non-deterministic  
computations (I'd be glad to receive comments!).


http://www-ps.informatik.uni-kiel.de/~sebf/pub/atps09.html

Now I recognise that one can also use FMList as the part that provides  
return and = and any Monoid for failure and choice.


Especially, one can implement breadth-first search (bfs) using a  
monoid that collects levels of a search tree and iterative deepening  
depth-first search (idfs) using a monoid that represents depth-bounded  
computations.


I have updated my package level-monad to use your library and monoids:

http://hackage.haskell.org/package/level-monad

The employed Monoid instances do not satisfy any monoid law. However,  
these are the simplest implementations of bfs and idfs that I am aware  
of, so I don't care very much ;)


Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sjoerd Visscher


On Jun 19, 2009, at 3:35 PM, Sjoerd Visscher wrote:


 transform t l = FM $ \f - unFM l (t f)

Unfortunately I couldn't get this code to type-check, so the library  
doesn't use transform.



With some help from Martijn van Steenbergen the type turned out to be:

transform :: (forall b. Monoid b = (a - b) - (c - b)) - FMList c - 
 FMList a


I've updated the library to use the transform function.
--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sjoerd Visscher


On Jun 19, 2009, at 5:06 PM, Sebastian Fischer wrote:

Your Monad and MonadPlus instances lead me to an interesting  
observation. Various strategies for non-deterministic search can be  
implemented using FMList by expressing failure and choice via a  
Monoid instance.


I have just finished a revision of a paper that explains how to  
factor two-continuation based backtracking (and other strategies)  
into a continuation monad transformer and a type class for non- 
deterministic computations (I'd be glad to receive comments!).


   http://www-ps.informatik.uni-kiel.de/~sebf/pub/atps09.html

Now I recognise that one can also use FMList as the part that  
provides return and = and any Monoid for failure and choice.


Especially, one can implement breadth-first search (bfs) using a  
monoid that collects levels of a search tree and iterative deepening  
depth-first search (idfs) using a monoid that represents depth- 
bounded computations.


I have updated my package level-monad to use your library and monoids:

   http://hackage.haskell.org/package/level-monad

The employed Monoid instances do not satisfy any monoid law.  
However, these are the simplest implementations of bfs and idfs that  
I am aware of, so I don't care very much ;)



Very nice. It is cool to see someone using this already! I see you did  
performance tests. How does your current version compare to f.e. one  
based on DiffLists?


I wonder though, aren't you worried that updated versions of FMList  
might use the monoid laws to rewrite certains bits, and your code  
would break? Essentially you are using FMLists as a tree structure,  
which isn't possible when you abide by the monoid laws.


I think you should be able to do the same thing in as many lines,  
using f.e. the ChoiceT type from MonadLib, where bfs and idfsBy are  
variations on runChoiceT. The ChoiceEff part might complicate things a  
bit though. But I might be missing some essential detail.


greetings,
--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE fmlist

2009-06-18 Thread Sjoerd Visscher
I am pleased to announce the first release of Data.FMList, lists  
represented by their foldMap function:
 newtype FMList a = FM { unFM :: forall b . Monoid b = (a - b) -  
b }

It has O(1) cons, snoc and append, just like difference lists.
Fusion is more or less built-in, for f.e. fmap and (=), but I'm not  
sure if this gives any advantages over what a compiler like GHC can do  
for regular lists.


My interest in this was purely the coding exercise, and I think there  
are some nice lines of code in there, for example:


 reverse l = FM $ \f - getDual $ unFM l (Dual . f)

If you like folds or monoids, you certainly should take a look.

One fun example:

 -- A right-infinite list
 c = 1 `cons` c
 -- A left-infinite list
 d = d `snoc` 2
 -- A middle-infinite list ??
 e = c `append` d

*Main head e
1
*Main last e
2

Install it with

  cabal install fmlist

Or go to

  http://hackage.haskell.org/package/fmlist-0.1

I owe a big thanks to Oleg Kiselyov, who wrote some of the more  
complicated folds in

http://okmij.org/ftp/Haskell/zip-folds.lhs
I don't think I could have come up with the zipWith code.

This is my first package on Hackage, so any comments are welcome!

greetings,
Sjoerd Visscher

PS. What happened to the traverse encoded containers (see below)? It  
turns out that it is a bit too generic, and functions like filter were  
impossible to implement. FMLists still have a Traversable instance,  
but only because the tree structure is (almost) undetectable, so they  
can simply be rebuilt using cons and empty.


On Jun 15, 2009, at 1:29 AM, Sjoerd Visscher wrote:


Hi,

While playing with Church Encodings of data structures, I realized  
there are generalisations in the same way Data.Foldable and  
Data.Traversable are generalisations of lists.


The normal Church Encoding of lists is like this:

 newtype List a = L { unL :: forall b. (a - b - b) - b - b }

It represents a list by a right fold:

 foldr f z l = unL l f z

List can be constructed with cons and nil:

 nil  = L $ \f - id
 cons a l = L $ \f - f a . unL l f

Oleg has written about this: http://okmij.org/ftp/Haskell/zip- 
folds.lhs


Now function of type (b - b) are endomorphisms which have a  
Data.Monoid instance, so the type can be generalized:


 newtype FM a = FM { unFM :: forall b. Monoid b = (a - b) - b }
 fmnil  = FM $ \f - mempty
 fmcons a l = FM $ \f - f a `mappend` unFM l f

Now lists are represented by (almost) their foldMap function:

 instance Foldable FM where
   foldMap = flip unFM

But notice that there is now nothing list specific in the FM type,  
nothing prevents us to add other constructor functions.


 fmsnoc l a = FM $ \f - unFM l f `mappend` f a
 fmlist = fmcons 2 $ fmcons 3 $ fmnil `fmsnoc` 4 `fmsnoc` 5

*Main getProduct $ foldMap Product fmlist
120

Now that we have a container type represented by foldMap, there's  
nothing stopping us to do a container type represented by traverse  
from Data.Traversable:


{-# LANGUAGE RankNTypes #-}

import Data.Monoid
import Data.Foldable
import Data.Traversable
import Control.Monad
import Control.Applicative

newtype Container a = C { travC :: forall f b . Applicative f = (a - 
 f b) - f (Container b) }


czero :: Container a
cpure :: a - Container a
ccons :: a - Container a - Container a
csnoc :: Container a - a - Container a
cpair :: Container a - Container a - Container a
cnode :: Container a - a - Container a - Container a
ctree :: a - Container (Container a) - Container a
cflat :: Container (Container a) - Container a

czero   = C $ \f - pure czero
cpure x = C $ \f - cpure $ f x
ccons x l   = C $ \f - ccons $ f x * travC l f
csnoc l x   = C $ \f - csnoc $ travC l f * f x
cpair l r   = C $ \f - cpair $ travC l f * travC r f
cnode l x r = C $ \f - cnode $ travC l f * f x * travC r f
ctree x l   = C $ \f - ctree $ f x * travC l (traverse f)
cflat l = C $ \f - cflat $ travC l (traverse f)

instance Functor Container where
 fmap g c = C $ \f - travC c (f . g)
instance Foldable Container where
 foldMap  = foldMapDefault
instance Traversable Container where
 traverse = flip travC
instance Monad Container where
 return   = cpure
 m = f  = cflat $ fmap f m
instance Monoid (Container a) where
 mempty   = czero
 mappend  = cpair

Note that there are all kinds of constructors, and they can all be  
combined. Writing their definitions is similar to how you would  
write Traversable instances.


So I'm not sure what we have here, as I just ran into it, I wasn't  
looking for a solution to a problem. It is also all quite abstract,  
and I'm not sure I understand what is going on everywhere. Is this  
useful? Has this been done before? Are there better implementations  
of foldMap and (=) for Container?


Finally, a little example. A Show instance (for debugging purposes)  
which shows the nesting structure.


newtype ShowContainer a = ShowContainer { doShowContainer :: String }
instance Functor ShowContainer where
 fmap _ (ShowContainer x) = ShowContainer $ ( ++ x 

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-18 Thread Sebastian Fischer

On Jun 18, 2009, at 9:57 AM, Sjoerd Visscher wrote:

I am pleased to announce the first release of Data.FMList, lists  
represented by their foldMap function: [...]

http://hackage.haskell.org/package/fmlist-0.1


cool!

Just for fun: a derivation translating between different formulations  
of monadic bind.


m = g
  = flatten (fmap g m)
  = FM $ \f - unFM (fmap g m) (foldMap f)
  = FM $ \f - unFM (FM $ \f' - unFM m (f' . g)) (foldMap f)
  = FM $ \f - (\f' - unFM m (f' . g)) (foldMap f)
  = FM $ \f - unFM m (folfMap f . g) -- your definition
  = FM $ \f - unFM m (flip unFM f . g)
  = FM $ \f - unFM m (\x - flip unFM f (g x))
  = FM $ \f - unFM m (\x - unFM (g x) f)-- like  
continuation monad


Cheers,
Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)





PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe