Code from "Why Functional Programming Matters"

I've been reading the classic "Why functional programming matters" paper [1] lately, particularly looking at the alpha beta stuff. I've ported all his code to haskell, but I have a question. His algorithm takes a board position, creates a gametree out of it, maps a static evaluation function over the gametree, then uses alpha beta to find the real evaluation from a Tree Int. But of course, in an actual application, what you actually want is the best MOVE from the current position (or, even more ideally, the so-called "principal variation", which is the best series of moves from the current position). Is there a good way to collect this, without mapping some sort of function over the tree that puts a list of moves on every node too? Hughes seems to completely ignore this, and I wonder if it's because it gets ugly to implement.

On Mon, 3 Sep 2007, Andrew Wagner wrote:
I've been reading the classic "Why functional programming matters" paper [1] lately, particularly looking at the alpha beta stuff. I've ported all his code to haskell, but I have a question.
His algorithm takes a board position, creates a gametree out of it, maps a static evaluation function over the gametree, then uses alpha beta to find the real evaluation from a Tree Int. But of course, in an actual application, what you actually want is the best MOVE from the current position (or, even more ideally, the so-called "principal variation", which is the best series of moves from the current position). Is there a good way to collect this, without mapping some sort of function over the tree that puts a list of moves on every node too?
I think he respects that, because every node in the game tree represents one possible state of the game. The "static" evaluation function pays attention to all information of each possible "current position".

On Mon, 2007-09-03 at 15:35 -0400, Andrew Wagner wrote:
I've been reading the classic "Why functional programming matters" paper [1] lately, particularly looking at the alpha beta stuff. I've ported all his code to haskell, but I have a question.
His algorithm takes a board position, creates a gametree out of it, maps a static evaluation function over the gametree, then uses alpha beta to find the real evaluation from a Tree Int. But of course, in an actual application, what you actually want is the best MOVE from the current position (or, even more ideally, the so-called "principal variation", which is the best series of moves from the current position). Is there a good way to collect this, without mapping some sort of function over the tree that puts a list of moves on every node too?
Hughes seems to completely ignore this, and I wonder if it's because it gets ugly to implement.
You have the current position, you have all the moves you can make from that position (conveniently provided by moves no less). You evaluate gametree on the new position made by making each of those moves and pick the best. There are issues with this, but it should be straightforward to label the "edges" and keep track of the path as you explore the tree.

I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy mzero `mplus` x = x x `mplus` mzero = x mzero >>= f = mzero v >> mzero = mzero but is that all there is to it? Are there no other requirements for MonadPlus to make sense? I also wondered why, once MonadPlus was added to the language, the definition of ++ wasn't changed to (++) = MonadPlus (with the MonadPlus instance for [] defined directly). Aside from getting msum and guard, is there any point in bothering to make something an instance of MonadPlus?

On Wed, Sep 05, 2007 at 03:35:03PM +1200, ok wrote:
I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy
mzero `mplus` x = x x `mplus` mzero = x mzero >>= f = mzero v >> mzero = mzero
but is that all there is to it? Are there no other requirements for MonadPlus to make sense?
I also wondered why, once MonadPlus was added to the language, the definition of ++ wasn't changed to (++) = MonadPlus (with the MonadPlus instance for [] defined directly).
It was. They changed it back in Haskell 98, as part of a grand program of dumbing down the langauge... Cale Gibbard says {{{I get the impression there were a lot of people on the Haskell 98 committee who really really hated polymorphism.}}}. Stefan

On 9/4/07, ok
I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy
mzero `mplus` x = x x `mplus` mzero = x mzero >>= f = mzero v >> mzero = mzero
but is that all there is to it? Are there no other requirements for MonadPlus to make sense?
Also, mplus has to be associative. I.e. (a `mplus` b) `mplus` c == a `mplus` (b `mplus` c)
I also wondered why, once MonadPlus was added to the language, the definition of ++ wasn't changed to (++) = MonadPlus (with the MonadPlus instance for [] defined directly).
You mean (++) = mplus. I've wondered that too. Similarly, one should define map = fmap. And a lot of standard list functions can be generalized to MonadPlus, for example you can define filter :: (MonadPlus m) => (a -> Bool) -> m a -> m a (This is not the same as filterM.)

On Tue, 4 Sep 2007, David Benbennick wrote:
On 9/4/07, ok
wrote: I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy
mzero `mplus` x = x x `mplus` mzero = x mzero >>= f = mzero v >> mzero = mzero
but is that all there is to it? Are there no other requirements for MonadPlus to make sense?
Also, mplus has to be associative. I.e. (a `mplus` b) `mplus` c == a `mplus` (b `mplus` c)
I also wondered why, once MonadPlus was added to the language, the definition of ++ wasn't changed to (++) = MonadPlus (with the MonadPlus instance for [] defined directly).
You mean (++) = mplus. I've wondered that too. Similarly, one should define map = fmap.
I think it is very sensible to define the generalized function in terms of the specific one, not vice versa.
And a lot of standard list functions can be generalized to MonadPlus, for example you can define
filter :: (MonadPlus m) => (a -> Bool) -> m a -> m a
Always using the most generalized form is not a good idea. If you know you are working on lists, 'map' and 'filter' tell the reader, that they are working on lists. The reader of a program doesn't need to start human type inference to deduce this. Also the type inference of the compiler will fail, if you write too general. Say, you are in GHCi, have your definition of 'filter' and you write Prelude> filter Char.isUpper (return 'a') To what monad this shall be specialised? Rely on type defaulting? Ok, you can use type signatures. See also: http://www.haskell.org/haskellwiki/Slim_instance_declaration

On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:
I think it is very sensible to define the generalized function in terms of the specific one, not vice versa.
The specific point at issue is that I would rather use ++ than `mplus`. In every case where both are defined, they agree, so it is rather frustrating to be blocked from using an operator which would otherwise have been appropriate. Of course it is not a show-stopper; I can simply make something else up. I am a little puzzled that there seems to be no connection between MonadPlus and Monoid. Monoid requires a unit and an associative binary operator. So does MonadPlus. Unfortunately, they have different names. If only we'd had (Monoid m, Monad m) => MonadPlus m...

On Wed, 5 Sep 2007, ok wrote:
On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:
I think it is very sensible to define the generalized function in terms of the specific one, not vice versa.
The specific point at issue is that I would rather use ++ than `mplus`. In every case where both are defined, they agree, so it is rather frustrating to be blocked from using an operator which would otherwise have been appropriate.
What is your application, where you need (++) frequently? Today I like that (++) points me to the fact, that we are working on lists. Ok, I would be fine, if (++) would be a method for all sequence types. But for MonadPlus, this is too general for my taste.
I am a little puzzled that there seems to be no connection between MonadPlus and Monoid. Monoid requires a unit and an associative binary operator. So does MonadPlus. Unfortunately, they have different names. If only we'd had (Monoid m, Monad m) => MonadPlus m...
Monoid is of kind * MonadPlus is of kind * -> *

ok wrote:
On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:
I think it is very sensible to define the generalized function in terms of the specific one, not vice versa.
The specific point at issue is that I would rather use ++ than `mplus`. In every case where both are defined, they agree, so it is rather frustrating to be blocked from using an operator which would otherwise have been appropriate.
You can. Just write: (++) = mplus in your programs (or in a module called OK.Utils or OK.Prelude!) and you can use ++. It's not (normally) a big problem to rename functions in haskell.
I am a little puzzled that there seems to be no connection between MonadPlus and Monoid. Monoid requires a unit and an associative binary operator. So does MonadPlus. Unfortunately, they have different names. If only we'd had (Monoid m, Monad m) => MonadPlus m...
The correct connection is: instance (Monoid (m a), Monad m) => MonadPlus m where mplus = mappend mzero = mempty Except, of course, we can't reasonably require that. Because for any one Monad m, there will be many ways to make (m a) into a Monoid, and most of them will not form properly behaved MonadPlusses. The converse notion is safer: instance MonadPlus m => Monoid (m a) where mappend = mplus mempty = mzero And I think the main reason we don't have this version, is that we can't cope well with multiple instances. Many data types admit more than one natural Monoid, and we don't have the language features to support that very cleanly. For example, there is also the Monoid: instance Monad m => Monoid (m ()) where mappend = (>>) mempty = return () and these two are not necessarily compatible. In fact, on [a] (or rather, [()]), the former gives us addition and the latter gives us multiplication, viewing [()] as isomorphic to Nat. These are two very well known monoids on Nat. Jules

David Benbennick wrote:
You mean (++) = mplus. I've wondered that too. Similarly, one should define map = fmap. And a lot of standard list functions can be generalized to MonadPlus, for example you can define
filter :: (MonadPlus m) => (a -> Bool) -> m a -> m a
Somehow this filter fails my intuition. Thanks to glguy on #haskell for showing me that you can define it as filter p m = m >>= \x -> if p x then return x else mzero I want filter to commute with mplus: (filter p m) `mplus` (filter p l) === filter p (m `plus` l) This is true for lists, and seems to me a natural requirement for filter to be considered, well, "a filter", along with the related filter p mzero == mzero. Unfortunately many of the MonadPlus instances we have don't satisfy that. Jules

G'day all.
Slight nit...
Quoting ok
I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy
mzero `mplus` x = x x `mplus` mzero = x mzero >>= f = mzero v >> mzero = mzero
As discussed previously, that last "law" is wrong. In particular, it can't be true of any monad transformer: lift fireMissiles >> mzero /= mzero
but is that all there is to it? Are there no other requirements for MonadPlus to make sense?
It's proposed to split nondeterminism-like monads and error catch-like monads to allow for some other laws: http://haskell.org/haskellwiki/MonadPlus_reform_proposal Cheers, Andrew Bromage

"Andrew Wagner"
current position (or, even more ideally, the so-called "principal variation", which is the best series of moves from the current position). Is there a good way to collect this, without mapping some sort of function over the tree that puts a list of moves on every node too?
Hughes seems to completely ignore this, and I wonder if it's because it gets ugly to implement.
While Hughes code looks nice, the more efficient you make your search the uglier it is going to be (at least with my Haskell skills) In reality you will at least want iterative deepening and principle variation search. I posted code for PVS (ugly code) http://www.haskell.org/haskellwiki/Principal_variation_search I thought I had some code doing iterative deepening based on this, but it looks like I lost it somewhere. If you want to use hash tables, history, killer moves, etc. Then I think you are going to have to monadize everything. It is a pity that Hughes doesn't demonstrate adding some of these things. Maybe it is possible using arrows? (without making everything look like C, which would be my solution). Rene.
participants (9)
-
ajb@spamcop.net
-
Andrew Wagner
-
David Benbennick
-
Derek Elkins
-
Henning Thielemann
-
Jules Bean
-
ok
-
Rene de Visser
-
Stefan O'Rear