[Haskell-cafe] Translating an imperative algorithm - negascout

Colin Paul Adams colin at colina.demon.co.uk
Thu Feb 26 15:54:19 EST 2009


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:

module Move (negascout
            ) where

{-# contract negascout Ok -> {depth | depth >= 0} ->
  Ok -> Ok -> Ok #-}
negascout :: Node -> Int -> Int -> Int -> Int
negascout node depth alpha beta =
    case depth == 0 || is_terminal node of
      True -> evaluate node
      False -> let child:rest = children node
                   b = beta  -- initial window is (-beta, -alpha)
               in negascout' child (depth-1) (- b) (- alpha) beta rest


-- Implementation

{-# contract negascout' Ok -> {depth | depth >= 0} ->
  Ok -> Ok -> Ok -> Ok -> Ok #-}    
negascout' :: Node -> Int -> Int -> Int -> Int -> [Node] -> Int
negascout' node depth beta' alpha beta rest =
    let a = negate $ negascout child depth beta' alpha
    in case a > (- alpha) of
         True -> let alpha' = a
                 in case alpha' >= beta of
                      True -> alpha' -- beta cut-off
                      False -> case alpha' >= (- beta') of -- null window failed high?
                                 True -> let alpha'' = negate $ negascout child depth (- beta) (- alpha') -- full re-search
                                         in case alpha'' >= beta of
                                                         True -> alpha'' -- beta cut-off
                                                         False -> case rest of
                                                                    [] -> alpha'' 
                                                                    child':rest' -> let b' = alpha'' + 1
                                                                                    in negascout' child' depth (- b') alpha'' beta rest'
                                            False -> case rest of
                                                       [] -> alpha'
                                                             child':rest' ->  let b' = alpha' + 1
                                                                              in negascout' child' depth (- b') alpha' beta rest'
                    False -> case rest of
                               [] -> alpha
                                     child':rest' ->  let b' = alpha + 1
                                                      in negascout' child' depth (- b') alpha beta rest'


-- 
Colin Adams
Preston Lancashire


More information about the Haskell-Cafe mailing list