Translating imperative algorithms to Haskell

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Hello! Four days ago I decided to try to learn Haskell by participating in Google AI Challenge (http://csclub.uwaterloo.ca/contest/). I went with LYAH and Real-World Haskell and I had no problems with functional core of Haskell, as I have lispy background. The problems begun when I tried to move my code to use different kind of decision algorithms, like negascout or flood fill. I have found a ready made solution for negascout (http://hackage.haskell.org/packages/archive/game-tree/0.1.0.0/doc/html/src/D...), but I was quite shocked by it's complexity, especially considering the relative easy of imperative algorithm.(http://en.wikipedia.org/wiki/Negascout). IMHO it is just TOO extremely complex and hard to read :/ In flood fill situation is similar - I need to track all the colored squares among 4 lines of recursion and I couldn't find a reasonable way to do it without going to infinite recursion or having lots of duplicates. So basically, I wonder if there is some generic way to transfer imperative algorithms with local state to functional style without making them overly complex. Thanks a lot, Mikhail -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.10 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkt+73cACgkQPHyh4sfuKrl7NgCeKHrIdJbHrSse6z7eRrmAi6ck yYoAoIRJZLq6RVUcCG2Zf5Xc5tRW5YBk =oUX7 -----END PGP SIGNATURE-----

Hi,
I recommend you read John Hughe's article "Why Functional Programming
Matters"[1]. As one of his examples he implements alpha-beta-pruning. I'm
not really a Haskell expert, but I think the main difference will be in the
kind of data structures you use to implement the algorithms. Many people
have recommended Chris Okasaki's PhD thesis [2] to me for an in-depth
treatment of the topic.
[1]: http://www.cs.chalmers.se/~rjmh/Papers/whyfp.htmlhttp://www.cs.chalmers.se/%7Erjmh/Papers/whyfp.html
[2]: http://www.cs.cmu.edu/~rwh/theses/okasaki.pdfhttp://www.cs.cmu.edu/%7Erwh/theses/okasaki.pdf
Best regards,
Marc
On Fri, Feb 19, 2010 at 9:07 PM, Mikhail Novikov
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
Hello!
Four days ago I decided to try to learn Haskell by participating in Google AI Challenge (http://csclub.uwaterloo.ca/contest/). I went with LYAH and Real-World Haskell and I had no problems with functional core of Haskell, as I have lispy background. The problems begun when I tried to move my code to use different kind of decision algorithms, like negascout or flood fill.
I have found a ready made solution for negascout ( http://hackage.haskell.org/packages/archive/game-tree/0.1.0.0/doc/html/src/D...), but I was quite shocked by it's complexity, especially considering the relative easy of imperative algorithm.( http://en.wikipedia.org/wiki/Negascout). IMHO it is just TOO extremely complex and hard to read :/
In flood fill situation is similar - I need to track all the colored squares among 4 lines of recursion and I couldn't find a reasonable way to do it without going to infinite recursion or having lots of duplicates.
So basically, I wonder if there is some generic way to transfer imperative algorithms with local state to functional style without making them overly complex.
Thanks a lot, Mikhail -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.10 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/
iEYEARECAAYFAkt+73cACgkQPHyh4sfuKrl7NgCeKHrIdJbHrSse6z7eRrmAi6ck yYoAoIRJZLq6RVUcCG2Zf5Xc5tRW5YBk =oUX7 -----END PGP SIGNATURE----- _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Feb 19, 2010 at 10:07:19PM +0200, Mikhail Novikov wrote:
So basically, I wonder if there is some generic way to transfer imperative algorithms with local state to functional style without making them overly complex.
It may be worthwhile to not translate at all. ST monad works as a charm :). Haskell is one of the best imperative languages. -- Felipe.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Hello! Maybe I should look into ST monad for this. :) I am still interested if there is a way to make this kind of functions in purely functional way. Best regards, Mikhail On 02/19/2010 11:18 PM, Felipe Lessa wrote:
On Fri, Feb 19, 2010 at 10:07:19PM +0200, Mikhail Novikov wrote:
So basically, I wonder if there is some generic way to transfer imperative algorithms with local state to functional style without making them overly complex.
It may be worthwhile to not translate at all. ST monad works as a charm :). Haskell is one of the best imperative languages.
-- Felipe. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.10 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkt/DHMACgkQPHyh4sfuKrlfBQCfdnN8qaHmP1B2YPqVqifwTAAU HLgAnih0r81xjOOmd7SYDWPjOWZ75YaK =5pBO -----END PGP SIGNATURE-----

On Fri, Feb 19, 2010 at 4:10 PM, Mikhail Novikov
Maybe I should look into ST monad for this. :) I am still interested if there is a way to make this kind of functions in purely functional way.
I *think* the answer to your question is "no". You can write imperative code in Haskell (via ST and IO), and you can write functional code that gets equivalent results to a given chunk of imperative code, but you can't directly translate imperative code to functional code, since they're two qualitatively different things. It's like asking to express a square in terms of a circle -- you can come up with a circle that has the same area, but it's definitely *not* a square. :-)

Hello all Particularly concerning the negascout algorithm, there doesn't seem to be much in the algorithm presented on Wikipedia that couldn't be done purely functionally with a fairly equivalent line count (might need a auxiliary tree type and a tree fold). The 'imperativeness' in this case only seems to be assignment to accumulators. The version on Hackage doesn't seem to define an actual tree data type only a tree-like type class, which while making things general does appear to make things complicated. Best wishes Stephen

Hello all How are search trees generated and what is their 'shape' - i.e. leaf labelled, node labelled, binary trees or rose trees? I've a functional reformulation of the Wikipedia algorithm which is about the same line count (excepting auxiliaries, which is a bit of a cheat), but its producing bad results on a leaf and node labelled rose tree. By the way, the imperative essence of the negascout algorithm and what makes it elegant is how it cuts off (control flow), rather than statefulness (assignment). Even though the line count is roughly the same and I believe I match the traversal behaviour / cut offs, the imperative version is simply nicer than my functional version. Best wishes Stephen

Stephen, Mikhail & all, I'll have a go... Wikipedia's imperative pseudo-code: function negascout(node, depth, α, β) if node is a terminal node or depth = 0 return the heuristic value of node b := β (* initial window is (-β, -α) *) foreach child of node a := -negascout (child, depth-1, -b, -α) if a>α α := a if α≥β return α (* Beta cut-off *) if α≥b (* check if null-window failed high*) α := -negascout(child, depth-1, -β, -α) (* full re-search *) if α≥β return α (* Beta cut-off *) b := α+1 (* set new null window *) return α My attempt to render into Haskell without ST monad and without attempting to understand the algorithm at all. Version 1 with lets negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha beta = ns (children node) alpha beta beta -- initial window is (-beta, -alpha) where ns (ch:chs) alpha beta b = let alpha' = alpha `max` negascout ch (depth-1) (-b) (-alpha) in if alpha' >= beta then alpha' else -- beta cut-off if alpha' >= b then -- full re-search let alpha'' = -negascout ch (depth-1) (-beta) (-alpha) in if alpha'' >= beta then alpha'' -- beta cut-off else ns chs alpha'' beta (alpha''+1) -- new window else ns chs alpha' beta (alpha'+1) -- new window ns [] alpha _ _ = alpha Version 2 with cases negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha beta = ns (children node) alpha beta -- initial window is (-beta, -alpha) where ns (ch:chs) alpha b = case alpha `max` negascout ch (depth-1) (-b) (-alpha) of alpha' | alpha' >= beta -> alpha' -- beta cut-off alpha' | alpha' >= b -> -- full re-search case -negascout ch (depth-1) (-beta) (-alpha) of alpha'' | alpha'' >= beta -> alpha'' -- beta cut-off alpha'' -> ns chs alpha'' (alpha''+1) -- new window alpha' -> ns chs alpha' (alpha'+1) -- new window ns [] alpha _ = alpha I think with case, it's slightly more readable. Marginally more verbose than the imperative version, because Haskell makes you do your state keeping more explicitly. Personally I find the Haskell easier to read. When I read the imperative version, it takes work to assemble in my head what is written out explicitly in the Haskell, but maybe that's just me. I certainly don't think the Haskell version is any more complex. I think there are cases where mutability is so important to an algorithm that Haskell struggles (at least in terms of performance), but I don't think this is one of those cases. Just for fun here's another version where I'm breaking it up into three parts: data Next a = Cont a | Break a breakableFoldl :: (a -> b -> Next a) -> a -> [b] -> a breakableFoldl body state xs = loop state xs where loop state [] = state loop state (x:xs) = case body state x of Cont state' -> loop state' xs Break state' -> state' negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha0 beta = alphaOut where (alphaOut, _) = breakableFoldl (\(alpha, b) ch -> (alpha `max` negascout ch (depth-1) (-b) (-alpha)) `betaCutoffOr` \alpha' -> if alpha' >= b then -- full re-search (-negascout ch (depth-1) (-beta) (-alpha)) `betaCutoffOr` \alpha'' -> Cont (alpha'', alpha''+1) else Cont (alpha', alpha'+1) ) (alpha0, beta) (children node) -- initial window is (-beta, -alpha) -- Break out if the input alpha value hits the beta cutoff, otherwise pass -- it to a non-cutoff case. betaCutoffOr :: Int -> (Int -> Next (Int,Int)) -> Next (Int,Int) betaCutoffOr alpha _ | alpha >= beta = Break (alpha, undefined) betaCutoffOr alpha nonCutoffCase = nonCutoffCase alpha This is a higher level of abstraction, which communicates intent fairly clearly, and shows how easily you can abstract common patterns out in Haskell. An improvement in this case? I think so, but there are arguments against that. Here's the missing code that makes each version above typecheck: data Node = Node { heuristic :: Int, children :: [Node] } terminal :: Node -> Bool terminal = undefined Steve Stephen Tetley wrote:
Hello all
How are search trees generated and what is their 'shape' - i.e. leaf labelled, node labelled, binary trees or rose trees?
I've a functional reformulation of the Wikipedia algorithm which is about the same line count (excepting auxiliaries, which is a bit of a cheat), but its producing bad results on a leaf and node labelled rose tree.
By the way, the imperative essence of the negascout algorithm and what makes it elegant is how it cuts off (control flow), rather than statefulness (assignment). Even though the line count is roughly the same and I believe I match the traversal behaviour / cut offs, the imperative version is simply nicer than my functional version.
Best wishes
Stephen _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

All, And... A slight variation that shadows alpha (which some people don't like, but I think it's a great technique) and thereby avoids the mistake I made in my previous three versions where I forgot a ' in -negascout ch (depth-1) (-beta) (-alpha'). (You have to watch that in Haskell.) data Next a = Cont a | Break a breakableFoldl :: (a -> b -> Next a) -> a -> [b] -> a breakableFoldl body state xs = loop state xs where loop state [] = state loop state (x:xs) = case body state x of Cont state' -> loop state' xs Break state' -> state' negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha0 beta = alphaOut where (alphaOut, _) = breakableFoldl (\(alpha, b) ch -> (alpha `max` negascout ch (depth-1) (-b) (-alpha)) `betaCutoffOr` \alpha -> if alpha >= b then -- full re-search (-negascout ch (depth-1) (-beta) (-alpha)) `betaCutoffOr` \alpha -> Cont (alpha, alpha+1) else Cont (alpha, alpha+1) ) (alpha0, beta) (children node) -- initial window is (-beta, -alpha) -- Break out if the input alpha value hits the beta cutoff, otherwise pass -- it to a non-cutoff case. betaCutoffOr :: Int -> (Int -> Next (Int,Int)) -> Next (Int,Int) betaCutoffOr alpha _ | alpha >= beta = Break (alpha, undefined) betaCutoffOr alpha nonCutoffCase = nonCutoffCase alpha Steve Stephen Blackheath [to Haskell-Beginners] wrote:
Stephen, Mikhail & all,
I'll have a go...
Wikipedia's imperative pseudo-code:
function negascout(node, depth, α, β) if node is a terminal node or depth = 0 return the heuristic value of node b := β (* initial window is (-β, -α) *) foreach child of node a := -negascout (child, depth-1, -b, -α) if a>α α := a if α≥β return α (* Beta cut-off *) if α≥b (* check if null-window failed high*) α := -negascout(child, depth-1, -β, -α) (* full re-search *) if α≥β return α (* Beta cut-off *) b := α+1 (* set new null window *) return α
My attempt to render into Haskell without ST monad and without attempting to understand the algorithm at all.
Version 1 with lets
negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha beta = ns (children node) alpha beta beta -- initial window is (-beta, -alpha) where ns (ch:chs) alpha beta b = let alpha' = alpha `max` negascout ch (depth-1) (-b) (-alpha) in if alpha' >= beta then alpha' else -- beta cut-off if alpha' >= b then -- full re-search let alpha'' = -negascout ch (depth-1) (-beta) (-alpha) in if alpha'' >= beta then alpha'' -- beta cut-off else ns chs alpha'' beta (alpha''+1) -- new window else ns chs alpha' beta (alpha'+1) -- new window ns [] alpha _ _ = alpha
Version 2 with cases
negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha beta = ns (children node) alpha beta -- initial window is (-beta, -alpha) where ns (ch:chs) alpha b = case alpha `max` negascout ch (depth-1) (-b) (-alpha) of alpha' | alpha' >= beta -> alpha' -- beta cut-off alpha' | alpha' >= b -> -- full re-search case -negascout ch (depth-1) (-beta) (-alpha) of alpha'' | alpha'' >= beta -> alpha'' -- beta cut-off alpha'' -> ns chs alpha'' (alpha''+1) -- new window alpha' -> ns chs alpha' (alpha'+1) -- new window ns [] alpha _ = alpha
I think with case, it's slightly more readable. Marginally more verbose than the imperative version, because Haskell makes you do your state keeping more explicitly. Personally I find the Haskell easier to read. When I read the imperative version, it takes work to assemble in my head what is written out explicitly in the Haskell, but maybe that's just me.
I certainly don't think the Haskell version is any more complex. I think there are cases where mutability is so important to an algorithm that Haskell struggles (at least in terms of performance), but I don't think this is one of those cases.
Just for fun here's another version where I'm breaking it up into three parts:
data Next a = Cont a | Break a
breakableFoldl :: (a -> b -> Next a) -> a -> [b] -> a breakableFoldl body state xs = loop state xs where loop state [] = state loop state (x:xs) = case body state x of Cont state' -> loop state' xs Break state' -> state'
negascout :: Node -> Int -> Int -> Int -> Int negascout node depth _ _ | terminal node || depth == 0 = heuristic node negascout node depth alpha0 beta = alphaOut where (alphaOut, _) = breakableFoldl (\(alpha, b) ch -> (alpha `max` negascout ch (depth-1) (-b) (-alpha)) `betaCutoffOr` \alpha' -> if alpha' >= b then -- full re-search (-negascout ch (depth-1) (-beta) (-alpha)) `betaCutoffOr` \alpha'' -> Cont (alpha'', alpha''+1) else Cont (alpha', alpha'+1) ) (alpha0, beta) (children node) -- initial window is (-beta, -alpha)
-- Break out if the input alpha value hits the beta cutoff, otherwise pass -- it to a non-cutoff case. betaCutoffOr :: Int -> (Int -> Next (Int,Int)) -> Next (Int,Int) betaCutoffOr alpha _ | alpha >= beta = Break (alpha, undefined) betaCutoffOr alpha nonCutoffCase = nonCutoffCase alpha
This is a higher level of abstraction, which communicates intent fairly clearly, and shows how easily you can abstract common patterns out in Haskell. An improvement in this case? I think so, but there are arguments against that.
Here's the missing code that makes each version above typecheck:
data Node = Node { heuristic :: Int, children :: [Node] }
terminal :: Node -> Bool terminal = undefined
Steve
Stephen Tetley wrote:
Hello all
How are search trees generated and what is their 'shape' - i.e. leaf labelled, node labelled, binary trees or rose trees?
I've a functional reformulation of the Wikipedia algorithm which is about the same line count (excepting auxiliaries, which is a bit of a cheat), but its producing bad results on a leaf and node labelled rose tree.
By the way, the imperative essence of the negascout algorithm and what makes it elegant is how it cuts off (control flow), rather than statefulness (assignment). Even though the line count is roughly the same and I believe I match the traversal behaviour / cut offs, the imperative version is simply nicer than my functional version.
Best wishes
Stephen _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Stephen
I'd be tempted to make the 'fold' problem specific (especially as I'm
not sure I'd call a fold a 'fold' if it breaks early).
Here's what I came up with though it seems to have a bug somewhere.
The Step and Window types might benefit strictness annos in real life.
The imperative version on Wikipedia is far clearer than either mine or
yours though.
Best wishes
Stephen
data Tree a = Node a [Tree a]
| Leaf a
deriving (Eq,Show)
data Step a = NewWindow a a
| BetaCutoff a
data Window a = Win a a
runCutoff :: [(Window a -> Step a)] -> Window a -> a
runCutoff [] (Win alp _) = alp
runCutoff (f:fs) ab = case f ab of
NewWindow a b -> runCutoff fs (Win a b)
BetaCutoff a -> a
cutoff :: a -> (a -> Bool) -> (a -> Step a) -> Step a
cutoff a test elsek | test a = BetaCutoff a
| otherwise = elsek a
negascout :: Tree Int -> Int -> (Window Int) -> Int
negascout (Leaf h) _ _ = h
negascout (Node h _ ) d _ | d <= 0 = h
negascout (Node _ ns) d w@(Win _ b0) = runCutoff (map scout ns) w
where
scout _ (Win a _) | a >= b0 = BetaCutoff a
scout node (Win a b) = let a' = max a (nega node (-b) (-a))
in cutoff a' (>= b0) (\x -> full node (Win x b))
full node (Win a b) = let a' = nega node (-b0) (-a)
in cutoff a' (>= b) (\x -> NewWindow x (x+1))
nega node x y = negate $ negascout node (d-1) (Win x y)
On 21 February 2010 19:29, Stephen Blackheath [to Haskell-Beginners]
All,
And... A slight variation that shadows alpha (which some people don't like, but I think it's a great technique) and thereby avoids the mistake I made in my previous three versions where I forgot a ' in -negascout ch (depth-1) (-beta) (-alpha'). (You have to watch that in Haskell.)

On Fri, Feb 19, 2010 at 4:17 PM, Tom Tobin
It's like asking to express a square in terms of a circle -- you can come up with a circle that has the same area
Heh, it was pointed out to me that you actually *can't* do this: http://en.wikipedia.org/wiki/Squaring_the_circle You can get a circle that has *approximately* the same area, but never exactly. Curse my lack of math background! ^_^
participants (6)
-
Felipe Lessa
-
Marc Dominik Migge
-
Mikhail Novikov
-
Stephen Blackheath [to Haskell-Beginners]
-
Stephen Tetley
-
Tom Tobin