[Haskell-cafe] Translating an imperative algorithm - negascout

Holger Siegel holgersiegel74 at yahoo.de
Fri Feb 27 07:32:27 EST 2009


Am Donnerstag, den 26.02.2009, 20:54 +0000 schrieb Colin Paul Adams:
> Hello Haskellers,
> 
> I want to implement the negascout algorithm for the game I'm writing.
> 
> Wikipedia gives the algorithm in imperative terms:
> 
> http://en.wikipedia.org/wiki/Negascout
> 
> I've tried to translate this into Haskell. I'm not sure if I'm going
> about it the right way, and if I am, if I've done it correctly.
> 
> 
> Any comments on my effort here, are welcome:

A more systematic transformation may lead to a more efficient
loop:

In the pseudocode, I have replaced the first conditional with the max
function and pulled the calculation of (depth - 1) out of the loop:

function negascout(node, depth, alpha, beta)
    if node is a terminal node or depth = 0
        return the heuristic value of node
    b := beta
    d := depth - 1
    foreach child of node
        alpha := max(alpha, -negascout (child, d, -b, -alpha))
        if alpha >= beta
            return alpha
        if alpha >= b
           alpha := -negascout(child, d, -beta, -alpha)
           if alpha >= beta
               return alpha
        b := alpha+1
    return alpha


In order to make this more Haskell-ish, we assume three self-explaining
functions:

> terminal        :: Node -> Bool
> heuristicValue  :: Node -> Int
> children        :: Node -> [a]

(Idiomatic) Haskell does not use mutable state or conditionals without
else-branch, so we make three modifications:

1) We use pattern matching for the first conditional
 
2) Every other conditional

     if c then a
     rest

   is rewritten as

     if c
     then do a
             rest
     else rest
     
   and

     do return x
        rest

   is abbreviated as

     return x

   (Here, 'return' is the imperative return statement, not the monadic
   unit)

3) We bring the program into single static assignment form. That is, we
   introduce new variables, so that every variable is assigned to only
   once. This is not always possible, because the loop would require
   us to introduce an unknown number of variables. Therefore, we allow
   reassignments at the end of an iteration.

And there it is, written in Haskell-like pseudocode:

> negascout :: Node -> Int -> Int -> Int -> Int
> negascout node depth alpha beta
>     | terminal node || depth == 0
>         = heuristicValue node
>     | otherwise
>         = do b := beta
>              d := depth - 1
>              foreach child of node do
>                  alpha' := max(alpha, - negascout child d (-b)
(-alpha))
>                  if alpha' >= beta
>                  then return alpha'
>                  else if alpha' >= b
>                       then do alpha'' := - negascout child d (-beta)
(-alpha')
>                               if alpha'' >= beta
>                               then return alpha''
>                               else do alpha := alpha''
>                                       b := alpha'' + 1
>                       else do alpha := alpha'
>                               b := alpha' + 1
>              return alpha

Now we see that only alpha and b are modified by the loop. From that it
follows how the loop can be turned into a recursive function: This
function takes alpha, b and the list of remaining children as its
argument:

> negascout node depth alpha beta
>    | terminal node || depth == 0
>        = heuristicValue node
>    | otherwise
>        = loop alpha beta (children node)
>    where
>    d = depth - 1
>    loop alpha b (c:cs) 
>        = let alpha' = max(alpha, - negascout c d (-b) (-alpha))
>          in if alpha' >= beta
>             then alpha'
>             else if alpha' >= b
>                  then let alpha'' = - negascout c d (-beta) (-alpha')
>                       in if alpha'' >= beta
>                          then alpha''
>                          else loop alpha'' (alpha'' + 1) cs 
>                  else loop alpha' (alpha' + 1) cs
>    loop alpha _ [] = alpha

Now you can move around the declarations, introduce some nice guards,
optimize the calls where b==alpha+1 or beta==alpha+1 and hunt for
hidden folds.

(Warning: I didn't test it)





More information about the Haskell-Cafe mailing list